Version 1.5 of ai05s/ai05-0149-1.txt

Unformatted version of ai05s/ai05-0149-1.txt version 1.5
Other versions for file ai05s/ai05-0149-1.txt

!standard 4.5.2(30.2/2)          09-06-06 AI05-0149-1/04
!standard 8.6(24)
!standard 8.6(25/2)
!standard 8.6(27/2)
!class Amendment 09-04-12
!status work item 09-04-12
!status received 09-04-12
!priority Medium
!difficulty Medium
!subject Access types conversion and membership
!summary
(See proposal.)
!problem
There is currently no way to check whether a conversion from an anonymous access type to a named access type will pass its run-time accessibility check. Normally a membership test can be used prior to a conversion to check if the conversion will succeed, but the current rules for access-type membership tests don't allow for this.
If an access type is made visible via a limited with, it can't be used in the client package to declare variables or components, since it is an incomplete type. (Note that in AI05-0151 we dicuss the possibility of using incomplete types for parameters and results.) In this case, it might be natural to use anonymous access types in the client package. However, these anonymous access types then need to be converted to the named access type at some point, and that currently requires an explicit conversion. It would be preferable if safe conversions from an anonymous access type to a named access type were implicit.
Finally, there seems no reason to require an explicit conversion to a named access-to-classwide type that is certain to succeed the tag check (i.e., is a "widening" conversion). This will reduce the need for anonymous access types in general, which is considered probably a good thing.
!proposal
This AI makes three related proposals:
1) When the tested type of a membership test is a general access
type, allow the expression to be of an anonymous access type.
2) Implicit conversion is provided from an anonymous access type
with a static accessibility level to a named, general access type, provided the explicit conversion is legal (i.e. static accessibility check passes; designated types match if untagged); further, if the designated type is tagged, the designated type of the anonymous access type shall be covered by the designated type of the named access type (explicit conversion allows for more possibilities).
3) Implicit conversion is provided from a named access type with a static
accessibility level to a named, general access-to-classwide type, provided the designated type of the target access type covers that of the source type. The usual static accessibility level check applies.
!wording
Add after 4.5.2(30.2/2):
* if the tested type is a general access-to-object type, the type of the simple_expression is convertible to the tested type and its accessibility level is no deeper than that of the tested type; further, if the designated type is tagged and the simple_expression is non-null, the tag of the object designated by the value of the simple_expression is covered by the designated type of the tested type.
Revise 8.6(22-25.1) as follows:
* If the expected type for a construct is a specific type T, then the type of the construct shall resolve either to T, or:
* to T'Class; or
* to a universal type that covers T; or
{* when T is a [Redundant: (named or anonymous)] general access-to-object
type (see 3.10) with designated type D'Class, to an access-to-object type whose designated type is covered by D'Class; or} [NOTE to ARG: this is relevant to parts (1) & (3)]
* when T is a specific anonymous access-to-object type (see 3.10) with designated type {a specific type} D, to an access-to-object type whose designated type is {D or} D'Class [or is covered by D]; or
{AARM Ramification: D'Class will only be legal as part of a call on a dispatching operation; see 3.9.2(9), "Dispatching Operations of Tagged Types". Note that that rule is not a Name Resolution Rule. }
{* when T is a named general access-to-object type (see 3.10) with
designated type a specific type D, to an anonymous access-to-object type whose designated type is also D; or} [NOTE to ARG: this is relevant to parts (1) & (2)]
* when T is an anonymous access-to-subprogram type (see 3.10), to an access-to-subprogram type whose designated profile is type-conformant with that of T.
Add after 8.6(27):
Other than for the simple_expression of a membership test, if the expected type for a name or expression is not the same as the actual type of the name or expression, the actual type shall be convertible to the expected type (see 4.6); further, if the expected type is a named access-to-object type and the actual type is an anonymous access-to-object type, then the name or expression shall denote a view with an accessibility level for which the statically deeper relationship applies [Redundant: ; in particular it shall not denote an access parameter nor a standalone access object].
{AARM NOTE: This is to minimize cases of implicit conversions when
the accessibility check cannot be performed at compile-time. We word this this way because access discriminants should also be disallowed if their enclosing object is designated by an access parameter.}
!discussion
We have grouped part (1) with these other proposals as any changes to the implicit conversion rules will affect the name resolution rules for membership.
The basic goal of (1) is that membership will return false if an attempt to convert the simple_expression into the tested type will be illegal or fail a run-time check.
We started from the approach used for tagged types, by allowing the simple_expression to be of any type that is convertible to the tested type. We then relaxed that to simplify name resolution, since we don't normally worry about things like static designated subtype matching in name resolution. We morphed the requirement for convertibility into a criteria for membership returning True.
We considered making a membership test illegal rather than returning False if the corresponding conversion would be illegal, but that didn't seem as friendly in places like generics, and there are currently no legality rules associated with membership tests.
We have limited it to access-to-object types, as there seems little need for the corresponding capability for access-to-subprogram types.
There are some places where run-time accessibility checks are performed other than conversions to a named type, and we aren't helping for those. But this seems like a simple improvement that handles many of the interesting cases of run-time accessibility checks.
The second part of this proposal addresses the implicit conversion of anonymous access types to named access types for everything but parameters. For parameters, AI05-0151 allows the original (incomplete) named access type to be used as a formal parameter type in the client package, rather than having to resort to an anonymous access type. Using anonymous access types for formal parameters introduces additional dynamic accessibility checks, whereas using the named access type directly avoids that.
The third part of this proposal provides the same level of implicit conversion for access-to-classwide types as is provided for classwide types directly. This part has more upward compatibility issues, so will require additional evaluation.
SAFETY CONCERNS:
For implicit conversion, we are only allowing it when the accessibility check is known to succeed statically. Since an explicit conversion is always available, there seems no reason to hide conversions that might in fact fail. Similarly, we are disallowing implicit "narrowing" conversions, which might fail a tag check. For example, if "type NT is new T with ..." we are disallowing an implicit conversion from anon acc-to-T'class to a named acc-to-NT'class, since there is a possibility that it will fail the tag check. Again, an explicit conversion is more appropriate here.
COMPATIBILITY CONCERNS:
Introducing additional implicit conversions from anonymous access types and/or to named access-to-classwide types could introduce some ambiguity into existing programs. For the conversions from an anonymous access type, this seems like a relatively small price to pay, as the ambiguity would occur under limited circumstances: the actual parameter is of an anonymous access type, and there are two functions with the same name differing only in that one has an access parameter where the other has a parameter of a named access type. Such a pair of functions would be ambiguous if the actual parameter were of the named access type, so it doesn't seem unreasonable that they would also end up ambiguous if the actual were of an anonymous type.
For the conversion to a named access-to-classwide type, this is perhaps more of a concern, as currently two subprograms that differ in the named access type of a parameter are not ambiguous unless the actual is "null" or an allocator. The extent of this ambiguity should be investigated if possible in existing archives of customer code. Note that this applies to some extent to both proposals (2) and (3), though more so to (3), as existing code could never pass an anonymous access type to a formal that is of a named access type.
!example
type Acc is access T; type Class_Acc is access T'Class;
procedure P(X : access T) is Y : Acc; Z : Class_Acc; begin Y := X; -- Illegal implicit conversion, since X is an access parameter. Y := Acc(X); -- Legal, might raise Program_Error
if X in Acc then Y := Acc(X); -- Known to be safe now else Y := null; end if;
Z := Y; -- Legal implicit conversion
Y := Z; -- Illegal implicit conversion end P;
!ACATS test
ACATS C-Tests are needed to check that this membership and these implicit conversions are allowed and (in the case of the membership) get appropriate results. A B-test is also needed for the legality rule.
!appendix

From: Franco Gasperoni
Date: Friday, November 14, 2008  1:54 PM

Right now a developer has no simple way to defend its code against accessibility
level problems, in particular should the user disable all checks.

To that extent we could define a new attribute 'Level, where for any entity E
for which an accessibility level is defined:

    E'Level returns a Natural which represents the accessibility
            level of E (better a private type with
            <, >, <=, >=, =, and a constant for the library_level
            and something to print it as an integer for teaching purposes)

As an example and using Natural for 'Level consider the following:

    package Pack is
       G : access Integer := new Integer'(0);
       --  G'Level = 0
       --  G.all'Level = 0

       procedure P (X : not null access Integer);
    end Pack;

    package body Pack is
       procedure P (X : not null access Integer) is
          --  X.all'Level = accessibility level of the object
                            pointed to by the actual

          Y : access Integer := G;
          --  Y'Level = 1
          --  Y.all'Level = 0
       begin
          null;
       end P;
    end Pack;

    with Pack; use Pack;
    procedure Main is
       W : aliased Integer;
       --  W'Level = 1
    begin
       P (G);
       --  Inside P, X.all'Level = 0

       P (W'Access);
       --  Inside P, X.all'Level = 1
    end Main;

Why is 'Level useful? Let's assume we have some preexisting code like

    type Cell is tagged record
       Next : access Cell'Class;
    end record;

    procedure Insert (X, Y : not null access Cell'Class) is;
    begin
       Y.Next := X.Next;
       Y.Next := Y;  --  Accessibility check we cannot defend against
    end;

If we use 'Level we can defend against the accessibility problem as follows

    procedure Insert (X, Y : not null access Cell'Class) is;
    begin
       if Y.all'Level <= X.Next'Level then
          Y.Next := X.Next;
          Y.Next := Y;
       else
          ...
       end if;
    end;

Note that if instead of "not null" the Y access parameter can be null then we
have to write

    procedure Insert (X : not null access Cell'Class;
                      Y :          access Cell'Class) is;
    begin
       if Y /= null and then Y.all'Level <= X.Next'Level then
          Y.Next := X.Next;
          Y.Next := Y;
       else
          ...
       end if;
    end;

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

From: Randy Brukardt
Date: Friday, November 14, 2008  3:28 PM

> Right now a developer has no simple way to defend its code against
> accessibility level problems, in particular should the user disable
> all checks.

I would be in favor of allowing more control of accessibility.

But I don't see any reason to worry about cases where the user has disabled all
checks (that is, pragma Suppress). By doing so, they are telling the compiler:
"I've thoroughly tested this program, and I'm certain that no checks are needed.
Make the program as fast as possible, but I understand that if I'm wrong that no
checks are needed, the program will fall over dead."

> To that extent we could define a new attribute 'Level, where
> for any entity E for which an accessibility level is defined:
>
>     E'Level returns a Natural which represents the accessibility
>             level of E (better a private type with
>             <, >, <=, >=, =, and a constant for the library_level
>             and something to print it as an integer for teaching purposes)

You seem to be confusing static and dynamic accessibility. This attribute would
presumably be testing the static accessibility (since you seem to expect that it
can be represented as an integer), which is not what the dynamic checks test.
Moreover, there is no way to easily describe dynamic accessibility, since
"incomparable" is a possible result. (It comes up with tasks and class-wide
types; if we generalized accessibility at all, it most likely would come up with
all access types as well.)

Steve points out that there ought to be a membership for accessibility, which
seems like a better idea (an operation to compare to accessibility of two
values, not a way to make that into an object). That probably would mitigate
your concern.

My thought on accessibility is that Tucker wants to extend dynamic accessibility
checks into more places (anonymous access returns; stand-alone objects). But
this is something that could be useful in all contexts. And it has a runtime
overhead, so declaring that you don't want it also would seem useful in all
contexts. (Specifically, it would be nice to be able to declare static
accessibility for an access parameter, if it is intended only to take existing
library level objects or some such. Dynamic accessibility always implies the
possibility of passing in something that causes something to break further down
the line, and that makes routines more fragile than they have to be.)

This comes back to Bob's idea that we don't really want features where you have
to do things a certain way (in this case, use anonymous access types) in order
to get some other useful but unrelated feature (dynamic accessibility checks).

So I wonder if it would make sense to allow an access type (*any* access type,
named or anonymous) to declare that it wants to use dynamic accessibility (or
static accessibility!) -- then the programmer can decide between the static
checks that never seem to actually work and dynamic checks that work but are
expensive.

One could go even further and allow an access type to have a static
accessibility that is deeper than where it is declared. (That would seem to have
value only for anonymous access types, so I don't think it is worth it.)

I haven't thought about the details of this idea too much, since I wanted to
find out if I was the only one thinking this way. So perhaps there is a giant
hole in it somewhere.

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

From: Franco Gasperoni
Date: Saturday, November 15, 2008  5:01 AM

> Steve points out that there ought to be a membership for
> accessibility, which seems like a better idea (an operation to compare
> to accessibility of two values, not a way to make that into an
> object). That probably would mitigate your concern.

Absolutely, that would solve it

> My thought on accessibility is that Tucker wants to extend dynamic
> accessibility checks into more places (anonymous access returns;
> stand-alone objects). But this is something that could be useful in all contexts.

Tuck is right on track there and I agree with your statement.

> And it
> has a runtime overhead, so declaring that you don't want it also would
> seem useful in all contexts. (Specifically, it would be nice to be
> able to declare static accessibility for an access parameter, if it is
> intended only to take existing library level objects or some such.
> Dynamic accessibility always implies the possibility of passing in
> something that causes something to break further down the line, and
> that makes routines more fragile than they have to be.)

Yes

> This comes back to Bob's idea that we don't really want features where
> you have to do things a certain way (in this case, use anonymous
> access types) in order to get some other useful but unrelated feature
> (dynamic accessibility checks).
>
> So I wonder if it would make sense to allow an access type (*any*
> access type, named or anonymous) to declare that it wants to use
> dynamic accessibility (or static accessibility!) -- then the
> programmer can decide between the static checks that never seem to
> actually work and dynamic checks that work but are expensive.

That is a very interesting thought indeed. In particular if we could "request"
and be guaranteed that all anonymous access to a given designated type T have
(say) static library-level accessibility then local anonymous allocators would
have to be allocated on the heap and would allow us to present anonymous access
as the natural match to the * T of C/C++ (except that it is safer :)

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

From: Tucker Taft
Sent: Wednesday, March 11, 2009  8:31 AM

Having an explicit level makes me nervous, especially since I presume it is
a static nesting level, whereas accessibility is actually officially defined
based on a dynamic nesting level, and in some cases, there is no simple static
nesting level that can be used instead.

What I would prefer would be to have a membership test properly report
whether a conversion of an anonymous access value to a named access type
would raise Program_Error *or* Constraint_Error.

E.g.:

       type Acc_T is access all T;

       X : Acc_T;

       procedure P(A : access T) is
       begin
          if A in Acc_T then
              X := Acc_T(A);  -- Won't raise P_E or C_E
          else
              -- Trouble, Acc_T(A) would raise P_E or C_E
              Put_Line("Can't convert to Acc_T");
          end if;
       end P;

    That is, a use of "A in Acc_T" would return False iff "Acc_T(A)"
    would raise Program_Error or Constraint_Error

Right now, such a membership test is not legal, since there are no implicit
conversions from anonymous access types to named access types, so we could add
this capability without incurring any upward incompatibility.

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

From: Gary Dismukes
Sent: Wednesday, March 11, 2009  11:58 AM

> What I would prefer would be to have a membership test properly report
> whether a conversion of an anonymous access value to a named access
> type would raise Program_Error
> *or* Constraint_Error.

Yes, I like that much better than tests using levels.  Making levels explicit
would be sure to run into tricky issues in some cases.

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

From: Bob Duff
Sent: Wednesday, March 11, 2009  12:51 PM

> What I would prefer would be to have a membership test properly report
> whether a conversion of an anonymous access value to a named access
> type would raise Program_Error
> *or* Constraint_Error.

Yes, I agree, that makes a lot of sense.

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

From: Randy Brukardt
Sent: Wednesday, March 11, 2009  3:21 PM

> Having an explicit level makes me nervous, especially since I presume
> it is a static nesting level, whereas accessibility is actually
> officially defined based on a dynamic nesting level, and in some
> cases, there is no simple static nesting level that can be used
> instead.

I pointed that out immediately after Franco posted the original message back
in November.

> What I would prefer would be to have a membership test properly report
> whether a conversion of an anonymous access value to a named access
> type would raise Program_Error
> *or* Constraint_Error.

And Steve Baird proposed something like this (in another thread) also back
in November. (That's how he got himself assigned to this accursed
subcommittee...)

> E.g.:
>
>        type Acc_T is access all T;
>
>        X : Acc_T;
>
>        procedure P(A : access T) is
>        begin
>           if A in Acc_T then
>               X := Acc_T(A);  -- Won't raise P_E or C_E
>           else
>               -- Trouble, Acc_T(A) would raise P_E or C_E
>               Put_Line("Can't convert to Acc_T");
>           end if;
>        end P;
>
>     That is, a use of "A in Acc_T" would return False iff "Acc_T(A)"
>     would raise Program_Error or Constraint_Error
>
> Right now, such a membership test is not legal, since there are no
> implicit conversions from anonymous access types to named access
> types, so we could add this capability without incurring any upward
> incompatibility.

...but thanks for working out the details. The main reason that I didn't make a
separate AI for this idea originally was that I couldn't figure out how it would
work.

OTOH, using a straight membership means that there is no such check possible for
named access types nor for anything else that has a dynamic accessibility check
(tagged returns, for instance). The problem seems more general than just anonymous
access parameters.

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

From: Tucker Taft
Sent: Sunday, April 12, 2009  8:46 PM

Here is my write-up of membership tests for accessibility.
[This is version /01 of the AI. - ED]
I basically piggy-backed on the change we made for tagged type, by requiring
that the simple_expression of a membership test resolve to a type that is
convertible to the tested type.  Seems like a pretty simple and natural fix.

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

From: Bob Duff
Sent: Monday, April 13, 2009  8:27 AM

> !proposal
>
> When the tested type of a membership test is a general access type,
> allow the expression to be of an anonymous access type.

That's not quite right -- the new wording allows additional tests for named types
as well.  Right?  Shouldn't it be "to be of any type convertible to the tested type,
including an anonymous access type"?

Other than that, I agree with the proposal.

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

From: Tucker Taft
Sent: Monday, April 13, 2009  8:37 AM

Good point.  Once I started the wording, it seemed simplest to allow any type
convertible to the tested type.  Requiring it to be anonymous would have required
more wording, to no obvious advantage.

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

From: Randy Brukardt
Sent: Thursday, April 30, 2009  1:05 AM

[A comment on version /02 of the AI - ED]

Why did you limit it to anonymous access type conversions? It's possibility to
convert between two (different) named general access types, and your previous
definition allowed it to be used in that case as well. That seemed like a good
thing to me (we want to avoid forcing people to use anonymous access types simply
because they get this feature). I realize it isn't that important, but it could be
useful in generic bodies, and it seems odd to explain this as wanting to be able
to test whether a conversion will succeed, and then not actually do that.

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

From: Tucker Taft
Sent: Thursday, April 30, 2009  1:34 AM

I didn't see the need for membership tests between two different named access types.
We don't have that for numeric types, even though conversions are allowed between then,
and it felt weird to me to extend membership tests in that way.  Tagged types are
different, in that there is a well-defined hierarchy, and conversion up and down the
hierarchy serves a different purpose than other kinds of conversions.

I did realize after writing up this new version that the original version allowed
membership tests across distinct named access types, but that seemed undesirable once
I realized it.

I suppose another reason to disallow membership tests across distinct named access types
is that it introduces more incompatibility due to added ambiguity.

Anyway, there are some reasons.  I'm not hard over on it, and I suppose membership tests
between two named access-to-tagged types might make some sense.  Membership tests between
two named access-to-untagged seems pretty hard to justify.

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

From: Randy Brukardt
Sent: Thursday, April 30, 2009  1:48 AM

> I did realize after writing up this new version that the original
> version allowed membership tests across distinct named access types,
> but that seemed undesirable once I realized it.

Humm, I thought it was a feature. And you described as one in your old writeup, that
why I noticed it was gone.

As I mentioned later, it seems useful in a generic body to see if converting to a
global type or a formal access type is possible (that would depend on where you are
instantiated). Not an important need though.

> I suppose another reason to disallow membership tests across distinct
> named access types is that it introduces more incompatibility due to
> added ambiguity.

Huh? What ambiguity could occur? Is there any useful membership allowed now (I
thought all you could do is test an object against its type, getting True; I doubt
there is much of that in programs!)

> Anyway, there are some reasons.  I'm not hard over on it, and I
> suppose membership tests between two named access-to-tagged types
> might make some sense.  Membership tests between two named
> access-to-untagged seems pretty hard to justify.

Well, I tried above. You can take it or leave it - this isn't an important issue,
just surprising to me.

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

From: Steve Baird
Sent: Thursday, April 30, 2009  12:50 PM

> I didn't see the need for membership tests between two different named
> access types.

I agree with Tuck on this issue.

Still, it seems like the wording to express this idea would be simpler if
the word "convertible" were used in place of something like "whose designated
type is the same as that of the tested type, or if tagged, convertible to the
designated type of the tested type".

Can't we make use of the existing definition of "convertible"
in much the same way as is already done in the tagged case?
Something like
    If the tested type is a general access-to-object type, then the
    simple_expression shall resolve to be of the tested type or of
    an anonymous type that is convertible to the the tested
    type.

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

From: Tucker Taft
Sent: Thursday, April 30, 2009  1:16 PM

I tried to explain why I dropped that albeit simpler wording in the !discussion
section.  The problem is that we don't normally expect the overload resolution
algorithm to deal with things as subtle as access-type convertibility.

In the case of access types, convertibility includes things like static matching
of designated subtypes, and static accessibility level comparisons.  Those would
be new things for overload resolution to worry about.  By contrast, the wording
I propose, though more complicated, is actually a pretty good match to existing
resolution rules between anonymous access types and named access types.

Interestingly, if we combine this with the other AI relating to "limited with
and access types," where we are proposing to allow implicit conversion *from*
anonymous access types *to* named access types in more contexts, this may simplify
again, back to something like normal expected-type resolution (though there might
be an added legality rule that would *not* apply to membership tests but *would*
apply in other "implicit conversion" contexts).

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

From: Tucker Taft
Sent: Tuesday, May 19, 2009  12:12 PM

Here is a very straightforward combination of ai-149 and ai-151, plus I added in
Bob's proposal that we allow implicit conversions to a named access-to-classwide
type from other *named* access types covered by it.  That is part (4) of this
4-part AI (not sure whether we have achieved 4-part harmony ;-).

[Ed: This is version /04 of this AI.]

I doubt I will have a chance to do much more with this AI before tomorrow.

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

From: Bob Duff
Sent: Tuesday, May 19, 2009  3:05 PM

> Here is a very straightforward combination of ai-149 and ai-151,

Looks good.

> plus I added in Bob's proposal that we allow implicit conversions to a
> named access-to-classwide type from other
> *named* access types covered by it.

Thanks!  That's the key feature.

>...That is part (4) of this
> 4-part AI (not sure whether we have achieved 4-part harmony ;-).

;-)

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

From: Steve Baird
Sent: Tuesday, May 19, 2009  6:42 PM

> This AI makes four related proposals:
>
> 1) When the tested type of a membership test is a general access
>    type, allow the expression to be of an anonymous access type.
>
> 2) Incomplete access types, which are access types declared in a
>    limited view of a package, may be used as formal parameter and result
>    types.
>
> 3) Implicit conversion is provided from an anonymous access type
>    with a static accessibility level to a named, general access type,
>    provided the explicit conversion is legal (i.e. static accessibility
>    check passes; designated types match if untagged); further, if the
>    designated type is tagged, the designated type of the anonymous
>    access type shall be covered by the designated type of the named
>    access type (explicit conversion allows for more possibilities).
>
> 4) Implicit conversion is provided from a named access type with a static
>    accessibility level to a named, general access-to-classwide type,
>    provided the designated type of the target access type covers that of
>    the source type.  The usual static accessibility level check applies.

#1, #3, and #4 look good.

I'm not so sure about #2.

The big question is whether leaning more heavily in any way on limited views is
a good idea.

I'm inclined to say no, but I don't feel strongly about it.

I'm more concerned about the details here.

> An incomplete access type is OK as a parameter or result since
> access-type parameters and results are always passed by copy, and the
> implementation can use a default general-access-type representation
> for them, even if the full named access type turns out to have some
> kind of aspect clause.

What makes me nervous here is presupposing the existence of a
general-access-type representation which can always be used for parameter
passing.

Suppose an implementation chooses to support something like

    type T is access Boolean;
    pragma Bit_Address (T);

or

   type T is access Some_Type;
   pragma Check_Magic_Number_Matching (T);
   -- access values include an id which is checked
   -- against an id value stored with the designated
   -- object upon dereference

or perhaps both.

An incomplete access type *might* turn out to be subject to such a pragma, so
this "default" representation must handle this case. So we get distributed
overhead if, for example, this forces the use of a representation which doesn't
fit in a register on the target machine.

Now we look at two procedures, each with a single parameter of the same access
type. For one, the access type was incomplete at the point of the subprogram
declaration. These two subprograms have to be compatible with respect to being
called via an access to subprogram value (similar considerations apply to
parameters/results of dispatching operations).

This means that an implementation must either use the "general" representation
even in the case where the full view of the access type is available or the
implementation must introduce wrappers.

I'm worried that we're opening a can of worms here.

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

From: Bob Duff
Sent: Tuesday, May 19, 2009  7:08 PM

>    type T is access Some_Type;
>    pragma Check_Magic_Number_Matching (T);
>    -- access values include an id which is checked
>    -- against an id value stored with the designated
>    -- object upon dereference

That's what some folks call a "generation count".

> or perhaps both.
>
> An incomplete access type *might* turn out to be subject to such a
> pragma, so this "default" representation must handle this case. So we
> get distributed overhead if, for example, this forces the use of a
> representation which doesn't fit in a register on the target machine.
>
> Now we look at two procedures, each with a single parameter of the
> same access type. For one, the access type was incomplete at the point
> of the subprogram declaration. These two subprograms have to be
> compatible with respect to being called via an access to subprogram
> value (similar considerations apply to parameters/results of
> dispatching operations).
>
> This means that an implementation must either use the "general"
> representation even in the case where the full view of the access type
> is available or the implementation must introduce wrappers.

These are implementation-defined pragmas, so they have implementation-defined
rules.  Can't the implementation just outlaw their use in the problematic cases?
Possibly at an "unusual" time, like when the two views "come together"
-- or even at link time?

Do you believe there's a problem with GNAT's fat pointers?

> I'm worried that we're opening a can of worms here.

Possibly.  Ichbiah always called it a "bag" of worms, by the way.  ;-)

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

From: Tucker Taft
Sent: Tuesday, May 19, 2009  9:36 PM

> What makes me nervous here is presupposing the existence of a
> general-access-type representation which can always be used for
> parameter passing.

Don't access parameters already presume that?  I think there might be an issue
with function results, but I don't understand how parameters can be a problem.
Similarly, explicit access conversion to a general access type presumes that any
access value can be represented as a value of a general access type with the
same designated subtype.  On the other hand, as Bob mentioned, these are
implementation-defined pragmas, so you can create any limitation you want
associated with them, both as far as conversion to a general access type, and
the "hidden" conversion that might take place to an incomplete view.

...
> An incomplete access type *might* turn out to be subject to such a
> pragma, so this "default" representation must handle this case. So we
> get distributed overhead if, for example, this forces the use of a
> representation which doesn't fit in a register on the target machine.

How would that work

> Now we look at two procedures, each with a single parameter of the
> same access type. For one, the access type was incomplete at the point
> of the subprogram declaration. These two subprograms have to be
> compatible with respect to being called via an access to subprogram
> value (similar considerations apply to parameters/results of
> dispatching operations).
>
> This means that an implementation must either use the "general"
> representation even in the case where the full view of the access type
> is available or the implementation must introduce wrappers.

I considered and then rejected making these subprograms have intrinsic calling
convention, because generating a wrapper seems very unlikely, and the
implementation could simply reject such uses if it so chose because these are
implementation-defined pragmas.

> I'm worried that we're opening a can of worms here.

Perhaps, though I think the implementation-defined nature of these pragmas
allows the implementator great flexibility.

A bigger concern for me would be the "fat pointer" situation. However, it
doesn't seem like such a big deal since we know that when the actual heap
objects are created, you would have a full view of the access type, so you could
create the appropriate kind of heap representation.  Then you will know it is
always safe to convert the presumably "general" fat pointer representation back
to the special "thin" pointer representation, since you know the bounds were in
fact placed contiguous with the array components.  That conversion would not in
general be safe since you wouldn't be sure where the bounds were allocated.  But
in this case, since the conversions are under control of the implementation,
everything is copacetic.

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

From: Steve Baird
Sent: Wednesday, May 20, 2009  12:01 AM

>> An incomplete access type *might* turn out to be subject to such a
>> pragma, so this "default" representation must handle this case. So
>> we get distributed overhead if, for example, this forces the use of
>> a representation which doesn't fit in a register on the target
>> machine.
>
> How would that work


If, for example, a Jumbo-format pointer is passed as a pair of
addresses, then a conservative assumption that a given incomplete
access type *might* have a Jumbo representation would (in the absence
of wrappers) require passing 2 addresses when a subprogram has a
parameter of this incomplete access type.

> I considered and then rejected making these subprograms have
> intrinsic calling convention, because generating a wrapper seems very
> unlikely, and the implementation could simply reject such uses if it
> so chose because these are implementation-defined pragmas.
>

True, although this might involve post-compilation checks.

>>
>> I'm worried that we're opening a can of worms here.
>
> Perhaps, though I think the implementation-defined nature of these
> pragmas allows the implementator great flexibility.
>
> A bigger concern for me would be the "fat pointer" situation.

I agree that that is a concern.
I think there are problems in this area.

> However, it doesn't seem like such a big deal since we know that when
> the actual heap objects are created, you would have a full view of
> the access type, so you could create the appropriate kind of heap
> representation.  Then you will know it is always safe to convert the
> presumably "general" fat pointer representation back to the special
> "thin" pointer representation, since you know the bounds were in fact
> placed contiguous with the array components.  That conversion would
> not in general be safe since you wouldn't be sure where the bounds
> were allocated.  But in this case, since the conversions are under
> control of the implementation, everything is copacetic.


There would be access-to-subprogram issues even for a pool-specific
access type. If two subprograms have the same parameter profile but
one expects to be passed a fat pointer and one expects a thin pointer,
then you need wrappers, right?

I think things get worse when we consider general access types because
in that case (I think; correct me if I'm wrong) we have to deal with
the case of a designated object which lacks a contiguous dope vector.

Just in general, it seems reasonable that an implementation might have
a strategy where the format of an access type depends on properties of
the designated type (with some default representation used in the case
of a Taft-amendment designated type).

Any time you have an access type which gets the non-default
representation, you're going to have problems with the incomplete view
of that access type.

As I mentioned earlier, this would require wrappers or some analogous
implementation work for both forms of dynamic call
(access-to-subprogram and dispatching operations).

If you have two interface types that both have an abstract operation
with the same name and profile, but one takes a parameter of an
incomplete access type and the other takes a parameter of the complete
access type and then you have a type which implements both of the
interfaces, this can all be made to work but it seems like a fair
amount of work.

I think there is a fair amount of implementation effort implicit in
this proposal.

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

From: Tucker Taft
Sent: Wednesday, May 20, 2009  9:42 AM

Would problems be simplified if we disallowed a call or 'Access on such a
subprogram at a place where there is only an incomplete view of one of the
formal parameter access types? That would seem to eliminate the need for
wrappers and default representations.

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

From: Steve Baird
Sent: Wednesday, May 20, 2009  9:58 AM

I need to think about this.
Currently when you declare an access-to-subprogram type, you have all the
information you'll ever need about the conventions for calling subprograms
designated by values of that type. You are suggesting that we abandon this rule.
It makes me nervous, but I don't see any specific problems right off the top of
my head.

I think you would also want to disallow subprogram bodies.

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

From: Steve Baird
Sent: Wednesday, May 20, 2009  10:01 AM

... and instantiations with formal access types (yes, this case is possible).

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

From: Tucker Taft
Sent: Wednesday, May 20, 2009  11:02 AM

An intriguing possibility here is to generally allow *any* incomplete type as a
parameter or result type in a subprogram declaration, or at least any incomplete
type that comes from the limited view of a package.  If we disallow calls,
'Access, bodies, and instantiations, but allow such subprograms to be declared,
then "limited with" becomes significantly more useful, as it doesn't impose much
of any restriction on the spec that has the limited with, so long as the
corresponding body and the callers have a non-limited with.

This would also eliminate the annoying distinction between derived and
non-derived access types inherent in this proposal.

The special case for incomplete tagged would simply be that you can do more with
a subprogram whose only use of incomplete types in its profile is as parameters
of an incomplete tagged type.

Comments?

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

From: Tucker Taft
Sent: Wednesday, May 20, 2009  11:12 AM

Effectively what this would mean is that for such a subprogram, no uses that
would "freeze" the subprogram would be permitted in a place where you only have
an incomplete view of the result type or one of the non-tagged parameter types.
The subprogram itself would effectively be frozen at the start of the
compilation unit that enclosed its body.

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

From: Bob Duff
Sent: Wednesday, May 20, 2009  11:47 AM

> An intriguing possibility here is to generally allow *any* incomplete
> type as a parameter or result type in a subprogram declaration, or at
> least any incomplete type that comes from the limited view of a
> package.  If we disallow calls, 'Access, bodies, and instantiations,
> but allow such subprograms to be declared, then "limited with"
> becomes significantly more useful, as it doesn't impose much of any
> restriction on the spec that has the limited with, so long as the
> corresponding body and the callers have a non-limited with.

I like it.  I'd go for "any incomplete type" -- why not?

> This would also eliminate the annoying distinction between derived and
> non-derived access types inherent in this proposal.

Shrug.  Derived access types are vanishingly rare.

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

From: Steve Baird
Sent: Wednesday, May 20, 2009  11:57 AM

This seems like a big change, but it might work.

Consider an implementation which associates implicit parameters with certain
kinds of source-level parameters (e,g, a dope parameter for a parameter of an
unconstrained array subtype, an Is_Constrained parameter for a non-in-mode
parameter of a discriminated type with defaults, etc.).

This means that at the point of the initial declaration of a subprogram, the set
of implicit parameters associated with the subprogram might not be known.

This is, I suppose, just one special case of not knowing the calling convention
information for the subprogram.

I believe that some (most? all?) Ada compilers currently rely on knowing this
information at this point, but do they fundamentally need to? I'm not sure.

P.S. I really like two aspects of this proposal - eliminating "the annoying
distinction between derived and non-derived access types" and the lack of any
requirement for extracting any more information from a limited view of a package
than the language already requires.

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

From: Steve Baird
Sent: Wednesday, May 20, 2009  12:05 PM

> Shrug.  Derived access types are vanishingly rare.

I agree, but it might be handy if they worked in the few cases where they come
up.

I am thinking about a situation where a user uses a derived type to get
limited-view visibility to a type declared in an instance:

    package P is
       package I is new G;
       type D is new I.Some_Access_Type;
    end P;

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

From: Ed Schonberg
Sent: Wednesday, May 20, 2009  2:12 AM

This is very appealing, but it will require some tweaking of freezing rules, no?
At the end of a spec you freeze the subprograms, which freezes their formals,
etc. Clearly nothing can be done with these incomplete types, so we need some
paragraph in 13.14 to make this legal.   Otherwise this is a very substantial
simplification.

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


Questions? Ask the ACAA Technical Agent