comp.lang.ada
 help / color / mirror / Atom feed
* Initialization and Finalization of limited object "returned" by a function
@ 2010-02-11  4:37 Hibou57 (Yannick Duchêne)
  2010-02-11  9:51 ` Hibou57 (Yannick Duchêne)
                   ` (2 more replies)
  0 siblings, 3 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-11  4:37 UTC (permalink / raw)


Hello boys and girls,

I'm actually experiencing an deeply unexpected behavior to me. Let me
explain in few words, before you go and dinner with the Test program
which will come later soon.

Limited types does not know what copy is. I always though a limited
type "returned" by a function, was Initialized when it was created and
finalized when the scope of its real instance (the function actual
invocation's target) was Finalized.

What a surprise to me to experience something different : limited
object Finalized right after Initialization.

The Test program comes as a single file for convenience (the two
packages it is built upon are defined in its declarative region). Copy/
paste, name it Test.adb (or any other name if ever you compiler don't
like this one), compile and run.

Read comments : every things is explained (as well as my initial
expectation) in there.

Side note : if this was really the legal behavior, I should urgently
go back to Ada basics. I will re-check the RM about all of what this
story relies anyway.


with Ada.Text_IO;
-- To give feedback about what's going on.
with Ada.Finalization;
-- For the implementation of Spies.Instance_Type.

procedure Test is
   -- This Test application exposes an (from the autor
   -- point of view) unexpected behaviour of limited objects
   -- "returned" by a function : a case of Finalization
   -- which occurs right after Initialization, even before
   -- the function "returning" the limited object
   -- has terminated.
   --
   -- This Test application is built around Dispatching,
   -- a package which defines the type which will make
   -- us meet the latter introduced behaviour, and Spies,
   -- a package, which will provide us the ability to see
   -- when exactly objects are Initialized and then Finalized.

   -- -------------------------------------------------------------
   -- Spies package (specification and body)

   package Spies is
      -- Provides a spy which is an object you
      -- may put in any scope (included record,
      -- protected and task type). It will tell
      -- tales you of Initialization and
      -- Finalization of the scope where it
      -- is intruded.

      type Instance_Type (Client_Name : access String) is
         limited private;
      -- It is limited, so that it could spy scope in
      -- limited types.
      -- It will report you what it is experiencing,
      -- displaying messages on the output stream. The
      -- message includes the Client_Name, which should
      -- be the name of a block or the name of a type.

   private

      type Instance_Type (Client_Name : access String) is
         new Ada.Finalization.Limited_Controlled
         with null record;
      -- When the host scope will be initialized,
      -- Limited_Controlled.Initialize will be invoked,
      -- the same with finalization. This is how
      -- this spy reports things it is experiencing.

      overriding procedure Initialize
        (Instance : in out Instance_Type);

      overriding procedure Finalize
        (Instance : in out Instance_Type);

   end Spies;

   package body Spies is

      overriding procedure Initialize
        (Instance : in out Instance_Type)
      is
         Me : Instance_Type renames Instance;
      begin
         Ada.Text_IO.Put_Line
           ("Spy : I am coping Initialization of " &
            Me.Client_Name.all &
            ".");
      end;

      overriding procedure Finalize
        (Instance : in out Instance_Type)
      is
         Me : Instance_Type renames Instance;
      begin
         Ada.Text_IO.Put_Line
           ("Spy : I am coping with Finalization of " &
            Me.Client_Name.all &
            ".");
      end;

   end Spies;

   -- -------------------------------------------------------------
   -- Dispatch package (specification and body)

   package Dispatch is
      -- Was initialy created to analyze the cause
      -- of a dispatching failure, thus the name of
      -- this package; Actually, it exposes an
      -- unexpected behaviour of limited objects
      -- created with New_Instance : objects are
      -- Finalized right after they are Initialized,
      -- even before the function New_Instance, which
      -- "returns" a limited type has terminated.
      -- The action take place in the implementation
      -- of New_Instance (see the package body).

      type Instance_Type is synchronized interface;
      subtype Instance_Class is Instance_Type'Class;
      procedure P (Instance : in out Instance_Type) is abstract;
      function New_Instance return Instance_Class;

   end Dispatch;

   package body Dispatch is

      -- For testing purpose, two different implementation
      -- of Instance_Class was defined.

      -- ----------------------------------------------------------
      -- A_Type

      protected type A_Type is new Instance_Type with
         overriding procedure P;
      private
         Spy : Spies.Instance_Type
           (Client_Name => new String'("A_Type"));
         -- Don't worry about memory leaks : it's for
         -- testing purpose only.
      end;

      protected body A_Type is
         overriding procedure P is
         begin
            Ada.Text_IO.Put_Line ("Invoked P of A_Type.");
         end;
      end;

      -- ----------------------------------------------------------
      -- B_Type

      protected type B_Type is new Instance_Type with
         overriding procedure P;
      private
         Spy : Spies.Instance_Type
           (Client_Name => new String'("B_Type"));
         -- Don't worry about memory leaks : it's for
         -- testing purpose only.
      end;

      protected body B_Type is
         overriding procedure P is
         begin
            Ada.Text_IO.Put_Line ("Invoked P of B_Type.");
         end;
      end;

      -- ----------------------------------------------------------
      -- Creating instance of the interface's class.

      function New_A return A_Type is
      -- Required by the actual GNAT GPL to return
      -- a class wide type from a function returning
      -- a limited type.
      begin
         return Result : A_Type do
            null;
         end return;
      end;

      function New_B return B_Type is
      -- Same motivations as for New_A.
      begin
         return Result : B_Type do
            null;
         end return;
      end;

      function New_Instance return Instance_Class is
      -- Returns either an A_Type or a B_Type.
      -- Change the corresponding extended return
      -- statement to switch from one to another.
      begin
         Ada.Text_IO.Put_Line
            ("New_Instance : Step 1 " &
             "(before return statement).");
         -- Here is where the action takes place.
         -- The message "Step 1" will be displayed before
         -- the spy intruded in A_Type, will report
         -- Initialization of Result. That's OK so far.
         -- See next step.
         return Result : Instance_Class := New_A do
            Ada.Text_IO.Put_Line
              ("New_Instance : Step 2 " &
               "(inside of return statement).");
            -- The message "Step 2" appears after the
            -- spy reports Finalization of Result.
            -- I suppose something is going wrong there,
            -- as the type is limited, Result is not
            -- really its instance : its real instance
            -- the target of the function "returning"
            -- the limited object.
            null;
         end return;
      end;

   end Dispatch;

   -- -------------------------------------------------------------
   -- Testing

   Tested_Interface : Dispatch.Instance_Class :=
     (Dispatch.New_Instance);
   -- Seems to never come into real existence.

begin
   Dispatch.P (Instance => Tested_Interface);
   -- This will raise an error, as unfortunately,
   -- the Tested_Interface instance is already finalized
   -- at this point (erroneous or legal behavior ?)
end Test;



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11  4:37 Initialization and Finalization of limited object "returned" by a function Hibou57 (Yannick Duchêne)
@ 2010-02-11  9:51 ` Hibou57 (Yannick Duchêne)
  2010-02-11 11:00 ` Ludovic Brenta
  2010-02-11 15:16 ` Robert A Duff
  2 siblings, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-11  9:51 UTC (permalink / raw)


Unless someone know a reason for an opposite interpretation, after
I've check the ARM, it seems indeed, things should be like I was
expecting.

[ARM 7.5(8.1/2)]
> For an aggregate of a limited type used to initialize an object as
> allowed above, the implementation shall not create a separate
> anonymous object for the aggregate. For a function_call of a type
> with a part that is of a task, protected, or explicitly limited
> record type that is used to initialize an object as allowed above,
> the implementation shall not create a separate return object (see
> 6.5) for the function_call. The aggregate or function_call shall be
> constructed directly in the new object.

[ARM 7.5(8.a/2)]
> Discussion: For a function_call, we only require
> build-in-place{build-in-place [partial]} for a limited type that
> would have been a return-by-reference type in Ada 95. We do this
> because we want to minimize disruption to Ada 95 implementations and
> users.

[ARM 7.5(9/2)]
> While it is allowed to write initializations of limited objects,
> such initializations never copy a limited object. The source of such
> an assignment operation must be an aggregate or function_call, and
> such aggregates and function_calls must be built directly in the
> target object. The following are consequences of the rules for
> limited types:

[ARM 7.5(9.a/2)]
> To be honest: This isn't quite true if the type can become
> nonlimited (see below); function_calls only are required to be
> build-in-place for “really” limited types.

[ARM 7.5(9.a/2)]
> As illustrated in 7.3.1, an untagged limited type can become
> nonlimited under certain circumstances.

[ARM 7.3.1(5/1)]
> For example, an array type whose component type is limited private
> becomes nonlimited if the full view of the component type is
> nonlimited and visible at some later place immediately within the
> declarative region in which the array type is declared. within the
> immediate scope of the array type. In such a case, the predefined
> "=" operator is implicitly declared at that place, and assignment is
> allowed after that place.

The latter, which would be the only one kind of exception, as stated
by [ARM 7.5(9.a/2)], does not apply in the example of the Test
program.

So I'm suspecting an error here : the object should indeed not be
Finalized when New_A or New_B terminates, as it do in Test.

All view are limited : public and private view. So no where a limited
view becomes a nonlimited view. Use of extended return statement is
made in all place. Although Tested_Interface is initialized via an
invocation of New_Instance, no Finalization occurs (as the spy shows)
when its scope terminates. Its initialized where it is expected to be
(in New_A and New_B), but it is Finalized at the wrong place, just
like if it was returned by copy.

Protected, and Task are indeed to be Initialized/Finalized the way I
was expecting :

[ARM 7.6(9.1-9.5)]
> 9.1/2 A type is said to need finalization if:{needs finalization}
> {type (needs finalization)}
> 9.2/2 * it is a controlled type, a task type or a protected type; or
> 9.3/2 * it has a component that needs finalization; or
> 9.4/2 * it is a limited type that has an access discriminant whose
>         designated type needs finalization; or
> 9.5/2 * it is one of a number of language-defined types that are
>         explicitly defined to need finalization.

And Protected/Task are obviously limited :

[ARM 3.9.4(5/2)]
> An interface with the reserved word limited, task, protected, or
> synchronized in its definition is termed, respectively, a limited
> interface, a task interface, a protected interface, or a
> synchronized interface. In addition,{interface (synchronized)
> [partial]} {interface (protected) [partial]} {interface (task)
> [partial]} {interface (limited) [partial]} {interface (nonlimited)
> [partial]} {synchronized interface} {protected interface} {task
> interface} {limited interface} {nonlimited interface} all task and
> protected interfaces are synchronized interfaces, and all
> synchronized interfaces are limited interfaces.

If I'm wrong, I do not figure where I'm wrong.



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11  4:37 Initialization and Finalization of limited object "returned" by a function Hibou57 (Yannick Duchêne)
  2010-02-11  9:51 ` Hibou57 (Yannick Duchêne)
@ 2010-02-11 11:00 ` Ludovic Brenta
  2010-02-11 11:33   ` Jean-Pierre Rosen
  2010-02-11 23:15   ` Hibou57 (Yannick Duchêne)
  2010-02-11 15:16 ` Robert A Duff
  2 siblings, 2 replies; 65+ messages in thread
From: Ludovic Brenta @ 2010-02-11 11:00 UTC (permalink / raw)


Yannick Duchêne wrote on comp.lang.ada:
>    Tested_Interface : Dispatch.Instance_Class :=
>      (Dispatch.New_Instance);

Here you are initializing with an aggregate that contains the result
of the function call. I suspect this triggers a compiler bug. What
happens if you remove the parentheses?

--
Ludovic Brenta.



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

* Re: Initialization and Finalization of limited object "returned" by a  function
  2010-02-11 11:00 ` Ludovic Brenta
@ 2010-02-11 11:33   ` Jean-Pierre Rosen
  2010-02-11 23:15   ` Hibou57 (Yannick Duchêne)
  1 sibling, 0 replies; 65+ messages in thread
From: Jean-Pierre Rosen @ 2010-02-11 11:33 UTC (permalink / raw)


Ludovic Brenta a �crit :
> Yannick Duch�ne wrote on comp.lang.ada:
>>    Tested_Interface : Dispatch.Instance_Class :=
>>      (Dispatch.New_Instance);
> 
> Here you are initializing with an aggregate that contains the result
> of the function call. I suspect this triggers a compiler bug. What
> happens if you remove the parentheses?
No, this is a parenthesized expression.
This (would be) syntactic ambiguity is the reason why an aggregate with
a single element must use named notation.

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



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11  4:37 Initialization and Finalization of limited object "returned" by a function Hibou57 (Yannick Duchêne)
  2010-02-11  9:51 ` Hibou57 (Yannick Duchêne)
  2010-02-11 11:00 ` Ludovic Brenta
@ 2010-02-11 15:16 ` Robert A Duff
  2010-02-11 17:40   ` Adam Beneschan
  2010-02-12  4:40   ` Hibou57 (Yannick Duchêne)
  2 siblings, 2 replies; 65+ messages in thread
From: Robert A Duff @ 2010-02-11 15:16 UTC (permalink / raw)


"Hibou57 (Yannick Duch�ne)" <yannick_duchene@yahoo.fr> writes:

> What a surprise to me to experience something different : limited
> object Finalized right after Initialization.

I'm not going to read your code carefully, but that doesn't
seem right.  If you have:

    X : T := F(...);

the result of F is "built in place" in X, and should be finalized
when the procedure containing X is left.

Here is some more info about limited function returns:

http://www.adacore.com/2007/09/24/ada-gem-10/

and 2 following gems.

>       function New_A return A_Type is
>       begin
>          return Result : A_Type do
>             null;
>          end return;

You can say "return Result : A_Type;" here.

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 15:16 ` Robert A Duff
@ 2010-02-11 17:40   ` Adam Beneschan
  2010-02-11 19:10     ` Robert A Duff
                       ` (3 more replies)
  2010-02-12  4:40   ` Hibou57 (Yannick Duchêne)
  1 sibling, 4 replies; 65+ messages in thread
From: Adam Beneschan @ 2010-02-11 17:40 UTC (permalink / raw)


On Feb 11, 7:16 am, Robert A Duff <bobd...@shell01.TheWorld.com>
wrote:
> "Hibou57 (Yannick Duchêne)" <yannick_duch...@yahoo.fr> writes:
>
> > What a surprise to me to experience something different : limited
> > object Finalized right after Initialization.
>
> I'm not going to read your code carefully, but that doesn't
> seem right.  If you have:
>
>     X : T := F(...);
>
> the result of F is "built in place" in X, and should be finalized
> when the procedure containing X is left.

Yes, I believe that's right, and it's spelled out clearly in the RM,
in sections 7.6(17.1/3-17.11/3 and especially 17.7/3), 6.5(5.8/3),
6.5(23/2), 7.6(4), and 3.10.2(10.1/2).

P.S. That was intended as sarcasm.  I think these references are
right, but some of them contain some of the nastiest language in the
RM.  If Yannick really wants to re-check the RM, as he mentioned, I
recommend having a bottle of Tylenol handy.  Or a few beers.

But more simply, as I understand it: (1) When you have an extended
return, the return object is used as the anonymous object that holds
the function result at the point of the function call, so it's not
finalized until the caller is done with the anonymous object; and (2)
when the object is built in place, the anonymous object "mutates into"
the new object and is not finalized (7.6(17.7/3)).  So yes, no
finalization should be done until X goes out of scope.

                                     -- Adam




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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 17:40   ` Adam Beneschan
@ 2010-02-11 19:10     ` Robert A Duff
  2010-02-11 21:51       ` Adam Beneschan
  2010-02-12  0:44     ` Randy Brukardt
                       ` (2 subsequent siblings)
  3 siblings, 1 reply; 65+ messages in thread
From: Robert A Duff @ 2010-02-11 19:10 UTC (permalink / raw)


Adam Beneschan <adam@irvine.com> writes:

> But more simply, as I understand it: (1) When you have an extended
> return, the return object is used as the anonymous object that holds
> the function result at the point of the function call, so it's not
> finalized until the caller is done with the anonymous object; and (2)
> when the object is built in place, the anonymous object "mutates into"
> the new object and is not finalized (7.6(17.7/3)).  So yes, no
> finalization should be done until X goes out of scope.

Just to be clear: There's nothing particularly special about
extended return statements, other than the fact that they
provide a name for the result.  Build-in-place is caused
by being immutably limited, and it works fine for old-fashioned
simple return statements.  Extended return syntax can
be used with both limited and non-limited.

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 19:10     ` Robert A Duff
@ 2010-02-11 21:51       ` Adam Beneschan
  2010-02-11 22:49         ` Hibou57 (Yannick Duchêne)
                           ` (3 more replies)
  0 siblings, 4 replies; 65+ messages in thread
From: Adam Beneschan @ 2010-02-11 21:51 UTC (permalink / raw)


On Feb 11, 11:10 am, Robert A Duff <bobd...@shell01.TheWorld.com>
wrote:
> Adam Beneschan <a...@irvine.com> writes:
> > But more simply, as I understand it: (1) When you have an extended
> > return, the return object is used as the anonymous object that holds
> > the function result at the point of the function call, so it's not
> > finalized until the caller is done with the anonymous object; and (2)
> > when the object is built in place, the anonymous object "mutates into"
> > the new object and is not finalized (7.6(17.7/3)).  So yes, no
> > finalization should be done until X goes out of scope.
>
> Just to be clear: There's nothing particularly special about
> extended return statements, other than the fact that they
> provide a name for the result.  

That last is an important distinction, however.  A function call
involves (conceptually) an anonymous object.  For a normal return (for
a non-limited type):

   return Some_Expression;

Some_Expression is computed and then assigned into the anonymous
object.  This assignment involves an Adjust.  Then, at some point,
whatever objects went into creating Some_Expression will get finalized
when the function exits.  If Some_Expression is a local variable, for
instance, that variable will get finalized.  If some other temporary
needs to be created in order to hold the value of Some_Expression,
that temporary will be finalized.

For an extended return,

   return R : T;

R is not a local variable, and it isn't "assigned" into the anonymous
object; thus, there's no Adjust, and R is not finalized when the
function returns (but the anonymous object will be finalized later,
except when it mutates into some other object).  I think that's the
point of the nasty language in 3.10.2(10.1).  Which is another way of
saying that R is a name for the result (as you said), not a distinct
object that gets copied to the result.  I thought it would be helpful
to point it out---not to you, but to other readers.  It's hardly a
trivial difference, and it's an important one to understand when
adjusts and finalizations are involved.  Anyway, I hope this helps
someone.

                                   -- Adam





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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 21:51       ` Adam Beneschan
@ 2010-02-11 22:49         ` Hibou57 (Yannick Duchêne)
  2010-02-11 22:53           ` Hibou57 (Yannick Duchêne)
  2010-02-12  1:05           ` Adam Beneschan
  2010-02-11 22:53         ` Robert A Duff
                           ` (2 subsequent siblings)
  3 siblings, 2 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-11 22:49 UTC (permalink / raw)


On 11 fév, 22:51, Adam Beneschan <a...@irvine.com> wrote:
> For an extended return,
>
>    return R : T;
>
> R is not a local variable, and it isn't "assigned" into the anonymous
> object; thus, there's no Adjust, and R is not finalized when the
> function returns
Yes

> (but the anonymous object will be finalized later,
Which anonymous object ?

> except when it mutates into some other object).
Ouch, requires clarifications (at least to me)

> I think that's the
> point of the nasty language in 3.10.2(10.1).
Do you suggest the behavior I'm experiencing is the expected one ?
(being nasty or not)

> Which is another way of
> saying that R is a name for the result (as you said),
What I was expecting, indeed

> not a distinct
> object that gets copied to the result.
I hope so : it's limited !

> I thought it would be helpful
> to point it out---not to you, but to other readers.  It's hardly a
> trivial difference, and it's an important one to understand when
> adjusts and finalizations are involved.  Anyway, I hope this helps
> someone.
Probably I'm one of the "other readers"

Well, I will later drive another experiment, a shorter one, as Robert/
Bob suggested the example source I gave was a bit too long to be
quickly studied.



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 21:51       ` Adam Beneschan
  2010-02-11 22:49         ` Hibou57 (Yannick Duchêne)
@ 2010-02-11 22:53         ` Robert A Duff
  2010-02-11 23:41           ` Adam Beneschan
  2010-02-12  5:25         ` Hibou57 (Yannick Duchêne)
  2010-02-12  9:27         ` Alex R. Mosteo
  3 siblings, 1 reply; 65+ messages in thread
From: Robert A Duff @ 2010-02-11 22:53 UTC (permalink / raw)


Adam Beneschan <adam@irvine.com> writes:

> On Feb 11, 11:10�am, Robert A Duff <bobd...@shell01.TheWorld.com>
> wrote:
>> Adam Beneschan <a...@irvine.com> writes:
>> > But more simply, as I understand it: (1) When you have an extended
>> > return, the return object is used as the anonymous object that holds
>> > the function result at the point of the function call, so it's not
>> > finalized until the caller is done with the anonymous object; and (2)
>> > when the object is built in place, the anonymous object "mutates into"
>> > the new object and is not finalized (7.6(17.7/3)). �So yes, no
>> > finalization should be done until X goes out of scope.
>>
>> Just to be clear: There's nothing particularly special about
>> extended return statements, other than the fact that they
>> provide a name for the result. �
>
> That last is an important distinction, however.  A function call
> involves (conceptually) an anonymous object.  For a normal return (for
> a non-limited type):
>
>    return Some_Expression;
>
> Some_Expression is computed and then assigned into the anonymous
> object.  This assignment involves an Adjust.  Then, at some point,
> whatever objects went into creating Some_Expression will get finalized
> when the function exits.  If Some_Expression is a local variable, for
> instance, that variable will get finalized.  If some other temporary
> needs to be created in order to hold the value of Some_Expression,
> that temporary will be finalized.

That's right for nonlimited types, but my point is that it is
not right for limited types.

For limited types, "return Some_Expression;" and
"return Result : constant T := Some_Expression;"
have identical effect.  Adjust is not called (there is no
Adjust in the limited case), and the result object
is not finalized when leaving the function.

Note that in the limited case, Some_Expression cannot
be the name of a local variable -- it can be a function
call or an aggregate.

So we can have a whole chain of calls.  E.g.:

    X : T := A(...); -- T is limited

and A says "return B(...);", and B says "return C(...);"
and C says "return T'(agg, reg, ate);" -- there's only
one result object.  The aggregate inside C is built directly
in variable X.  It is not finalized when leaving C, B, or A.

> For an extended return,
>
>    return R : T;

> R is not a local variable, and it isn't "assigned" into the anonymous
> object; thus, there's no Adjust, and R is not finalized when the
> function returns (but the anonymous object will be finalized later,
> except when it mutates into some other object).  I think that's the
> point of the nasty language in 3.10.2(10.1).  Which is another way of
> saying that R is a name for the result (as you said), not a distinct
> object that gets copied to the result.

It doesn't matter whether the result object has a name or not.
What matters is whether it's limited -- in the limited case,
the result object is NOT finalized when leaving the function.

>...I thought it would be helpful
> to point it out---not to you, but to other readers.  It's hardly a
> trivial difference, and it's an important one to understand when
> adjusts and finalizations are involved.  Anyway, I hope this helps
> someone.

Well, umm...  ;-)

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 22:49         ` Hibou57 (Yannick Duchêne)
@ 2010-02-11 22:53           ` Hibou57 (Yannick Duchêne)
  2010-02-11 23:08             ` Robert A Duff
  2010-02-12  1:05           ` Adam Beneschan
  1 sibling, 1 reply; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-11 22:53 UTC (permalink / raw)


Clarification about my words : what I've quoted from you, was talking
about extended return statement. I was understanding this as "extended
return statement applied to limited". If this was ever not what you
were talking about, there are chance I've understood what you were to
say. I will look again at the ARM reference you've pointed (as well as
the ones suggested in your previous post in this same thread).



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 22:53           ` Hibou57 (Yannick Duchêne)
@ 2010-02-11 23:08             ` Robert A Duff
  2010-02-11 23:18               ` Hibou57 (Yannick Duchêne)
                                 ` (3 more replies)
  0 siblings, 4 replies; 65+ messages in thread
From: Robert A Duff @ 2010-02-11 23:08 UTC (permalink / raw)


"Hibou57 (Yannick Duch�ne)" <yannick_duchene@yahoo.fr> writes:

> Clarification about my words : what I've quoted from you, was talking
> about extended return statement. I was understanding this as "extended
> return statement applied to limited".

Extended return statements are not much more than syntactic sugar.  They
don't change anything about when the result object is finalized.  All
they do is give you a name you can use to refer to the result object.
If there's no name, the result object is still there, but you can't
refer to it inside the function body.

Oh, I guess there's one other thing extended returns do -- they
allow you to default-initialize the result object:

    return X : T;

which can't be expressed with a simple return.

Extended return statements are important in the limited case,
because you often want to say something like "Result.X := ...;".
And as you discovered, aggregates aren't allowed for protected
or task types (which was probably a language design mistake).

Extended return statements are not so important for nonlimited types,
but they do come in handy in that case, too.

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 11:00 ` Ludovic Brenta
  2010-02-11 11:33   ` Jean-Pierre Rosen
@ 2010-02-11 23:15   ` Hibou57 (Yannick Duchêne)
  2010-02-11 23:24     ` Robert A Duff
  1 sibling, 1 reply; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-11 23:15 UTC (permalink / raw)


On 11 fév, 12:00, Ludovic Brenta <ludo...@ludovic-brenta.org> wrote:
> Yannick Duchêne wrote on comp.lang.ada:
>
> >    Tested_Interface : Dispatch.Instance_Class :=
> >      (Dispatch.New_Instance);
>
> Here you are initializing with an aggregate that contains the result
> of the function call. I suspect this triggers a compiler bug. What
> happens if you remove the parentheses?
As Jean-Pierre explained, this is not an aggregate, its a
parenthesized expression.

Let me explain why such a simple expression is parenthesized here :
this is just a matter of text layout. I follow one part of the
convention which is in use in the world of GNAT/GPS, which applies an
outdent of one character whenever a language construct which is able
to start with a parenthesis span multiple lines. This make sens for a
complex expression or an enumeration spanning multiple lines as an
example (in the latter example, the first parenthesis being outdent of
one character, the first item which comes next to it, has thus the
same indent as all the following items). But as this outdent is always
to be there, if the construct is not parenthesized, then the
indentation is not the expected one. So, when it happens a simple
expression has to stand to the next line, indented, just because it
would have otherwise go beyond the line width limit (which is 67
characters when I post example source on c.l.a), it turns to be a
simple expression with parenthesis.

That's true that a lot of parenthesized constructs of the Ada language
may seems ambiguous at first sight. But these potential ambiguities
are gracefully handled by some language rules intended for adjustment
and ambiguity removal, so that it is finally not ambiguous at all.



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 23:08             ` Robert A Duff
@ 2010-02-11 23:18               ` Hibou57 (Yannick Duchêne)
  2010-02-12  0:48               ` Randy Brukardt
                                 ` (2 subsequent siblings)
  3 siblings, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-11 23:18 UTC (permalink / raw)


On 12 fév, 00:08, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
> Extended return statements are not much more than syntactic sugar.
On my way, I feel it's not so much syntactic sugar and it's mostly
required. Otherwise, a local variable would have to be used, which
would look like a return by copy.

By the way, that's true I have make use of extended return where
simple return statement would have been sufficient.

I'm back to the remaining of your post now.



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 23:15   ` Hibou57 (Yannick Duchêne)
@ 2010-02-11 23:24     ` Robert A Duff
  2010-02-12  5:41       ` Hibou57 (Yannick Duchêne)
  0 siblings, 1 reply; 65+ messages in thread
From: Robert A Duff @ 2010-02-11 23:24 UTC (permalink / raw)


"Hibou57 (Yannick Duch�ne)" <yannick_duchene@yahoo.fr> writes:

> That's true that a lot of parenthesized constructs of the Ada language
> may seems ambiguous at first sight. But these potential ambiguities
> are gracefully handled by some language rules intended for adjustment
> and ambiguity removal, so that it is finally not ambiguous at all.

Well, I don't find it "graceful" that single-element positional
aggregates are not allowed.  And zero-element ones.  I think
it's just bad language design.

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 22:53         ` Robert A Duff
@ 2010-02-11 23:41           ` Adam Beneschan
  2010-02-12  0:22             ` Robert A Duff
  0 siblings, 1 reply; 65+ messages in thread
From: Adam Beneschan @ 2010-02-11 23:41 UTC (permalink / raw)


On Feb 11, 2:53 pm, Robert A Duff <bobd...@shell01.TheWorld.com>
wrote:

> It doesn't matter whether the result object has a name or not.
> What matters is whether it's limited -- in the limited case,
> the result object is NOT finalized when leaving the function.

But that's true even if it's nonlimited, right?  If NLT is non-
limited, and you say (inside function NLT_Func)

   return X : NLT do
     X.Component := ...
   end return;

X, which is now another name for the "anonymous result object" created
for the function call, is not finalized "when leaving the function".
It's finalized later.  If you say

   Y : NLT := NLT_Func(...);

it's finalized after being copied to Y (assuming it is not built in
place).  If you pass the result to some other function(s):

   Z : Type2 := Func2 (Func3 (NLT_Func (...)));

then I believe the result object (of NLT_Func) is not finalized until
after the entire expression is evaluated, right?

                                   -- Adam




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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 23:41           ` Adam Beneschan
@ 2010-02-12  0:22             ` Robert A Duff
  0 siblings, 0 replies; 65+ messages in thread
From: Robert A Duff @ 2010-02-12  0:22 UTC (permalink / raw)


Adam Beneschan <adam@irvine.com> writes:

> On Feb 11, 2:53�pm, Robert A Duff <bobd...@shell01.TheWorld.com>
> wrote:
>
>> It doesn't matter whether the result object has a name or not.
>> What matters is whether it's limited -- in the limited case,
>> the result object is NOT finalized when leaving the function.
>
> But that's true even if it's nonlimited, right?

Well, sort of.  In the nonlimited case, the result object
is copied somewhere, with adjust, and then finalized.
Except that the compiler is allowed to optimize that
away in some cases.  In the limited case, it must not
finalize the result object.

>...If NLT is non-
> limited, and you say (inside function NLT_Func)
>
>    return X : NLT do
>      X.Component := ...
>    end return;
>
> X, which is now another name for the "anonymous result object" created
> for the function call, is not finalized "when leaving the function".
> It's finalized later.  If you say
>
>    Y : NLT := NLT_Func(...);
>
> it's finalized after being copied to Y (assuming it is not built in
> place).

Yeah, OK, but "when leaving the function" and "after copying to Y"
are pretty much the same time.  And "when Y is finalized" is
a very-much-later time.

The finalization rules would be the same if the above return were

    return X : NLT := (Component => ..., others => <>);

or:

    return (Component => ..., others => <>);

My point was just that the "build in place" requirement is invoked by
limitedness, not by the syntax of the return statement.

By the way, I have on my "to do" list to implement build-in-place
in GNAT for NON-limited types, when possible.  That's just an
optimization.

>...If you pass the result to some other function(s):
>
>    Z : Type2 := Func2 (Func3 (NLT_Func (...)));
>
> then I believe the result object (of NLT_Func) is not finalized until
> after the entire expression is evaluated, right?

I don't remember the exact rules in this case.  As you say,
they're "nasty".  ;-)

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 17:40   ` Adam Beneschan
  2010-02-11 19:10     ` Robert A Duff
@ 2010-02-12  0:44     ` Randy Brukardt
  2010-02-12  4:47     ` Hibou57 (Yannick Duchêne)
  2010-02-12  4:49     ` Hibou57 (Yannick Duchêne)
  3 siblings, 0 replies; 65+ messages in thread
From: Randy Brukardt @ 2010-02-12  0:44 UTC (permalink / raw)


"Adam Beneschan" <adam@irvine.com> wrote in message 
news:d1d2586a-2f70-491a-8a12-01abae4ab6f5@t34g2000prm.googlegroups.com...
...
> Yes, I believe that's right, and it's spelled out clearly in the RM,
> in sections 7.6(17.1/3-17.11/3 and especially 17.7/3), 6.5(5.8/3),
> 6.5(23/2), 7.6(4), and 3.10.2(10.1/2).

Whether Adam was being sarastic or not, note that this semantics was totally 
rewritten after Amendment 1 was finished. And Adam is reading the new, much 
clearer text (that's relative, of course); the old text left so many 
questions unanswered that we gave up and started over. (Bob did much of the 
heavy lifting on that.)

Summary: He's looking at the draft Ada 2012 standard and not the Ada 2005 
one. Ada compilers are supposed to follow the new wording (it is a Binding 
Interpretation -- essentially a bug fix to the Standard), but there is no 
reason to assume that they do.

                      Randy.





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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 23:08             ` Robert A Duff
  2010-02-11 23:18               ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  0:48               ` Randy Brukardt
  2010-02-12  5:37               ` Hibou57 (Yannick Duchêne)
  2010-02-12  5:39               ` Hibou57 (Yannick Duchêne)
  3 siblings, 0 replies; 65+ messages in thread
From: Randy Brukardt @ 2010-02-12  0:48 UTC (permalink / raw)


"Robert A Duff" <bobduff@shell01.TheWorld.com> wrote in message 
news:wcc4olnid67.fsf@shell01.TheWorld.com...
...
> Extended return statements are important in the limited case,
> because you often want to say something like "Result.X := ...;".
> And as you discovered, aggregates aren't allowed for protected
> or task types (which was probably a language design mistake).

One that we tried to fix last time (for a while at least), but the attempt 
led us down quite a rabbit hole. Enough that Paris became snow-covered while 
we discussed it (and then returned to normal when we gave up). OK, maybe the 
snow had nothing to do with this topic of discussion, but it was memorable.

                            Randy.





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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 22:49         ` Hibou57 (Yannick Duchêne)
  2010-02-11 22:53           ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  1:05           ` Adam Beneschan
  2010-02-12  2:35             ` Hibou57 (Yannick Duchêne)
  1 sibling, 1 reply; 65+ messages in thread
From: Adam Beneschan @ 2010-02-12  1:05 UTC (permalink / raw)


On Feb 11, 2:49 pm, Hibou57 (Yannick Duchêne)
<yannick_duch...@yahoo.fr> wrote:
> On 11 fév, 22:51, Adam Beneschan <a...@irvine.com> wrote:> For an extended return,
>
> >    return R : T;
>
> > R is not a local variable, and it isn't "assigned" into the anonymous
> > object; thus, there's no Adjust, and R is not finalized when the
> > function returns
>
> Yes
>
> > (but the anonymous object will be finalized later,
>
> Which anonymous object ?

Any time you call a function, the language semantics say that there is
a "result object" to hold the function result.  The function is called
and puts its result in the result object.  The reason the language
calls it a distinct object is so that it can define when Adjusts and
finalizations take place for this object.

I may have erred by calling it an anonymous object.  In Ada 95, I
believe it was referred to as an anonymous object.  In Ada 2005, if
you use the extended return syntax, this gives a name to the result
object (as Bob said), so maybe it's wrong to call it "anonymous",
although there are parts of the RM that refer to "the anonymous object
representing the result of a function call" or words to that effect.
In any case, at the place where the function is called, you can't
refer to this result object by any name.

My earlier post may have been confusing because I was referring to two
separate parts of the function call process: (1) how the value gets
INTO the result object and (2) what the caller does with the result
object AFTER the function is finished.

For #1, when the function says

   return EXPR;

then EXPR is assigned into the result object (which means that an
Adjust has to be done), *unless* the result object gets built in
place, which is always the case if EXPR is a function call and the
type is limited.  But if the function says

   return NAME : TYPE [do ... end return];

then NAME is a name that *refers* to the result object; NAME does
*not* declare another object that will get assigned to the result
object as in the earlier example.

For #2, if you say

   X : T := Func(...);

The call to Func means that there is a "result object".  When Func is
called, the value gets put into the result object somehow, as
mentioned above.  Then, if X is not built in place, the result object
is copied to X, which means that an Adjust is done, and then the
result object is finalized.  However, if X *is* built in place (as it
must be if T is limited), then the call to Func puts a value into the
result object; and then after that point, X starts "magically"
referring to that result object.  There's no copying, and no
Finalize.  That's what the RM means by "mutating into".  Yes, the
language is a bit weird, and I know it was difficult for the ARG to
find the right words to express what was supposed to happen.

Anyway, the end result of all this is that, for a limited type (or in
any other case where X is built in place), there isn't supposed to be
any finalization until X disappears.  In your case, if you're seeing
your A_Type get finalized while Tested_Interface still exists, this is
incorrect behavior.

Hope this clears things up.  If instead I've just created more
confusion, I apologize and promise to refrain from making things worse
by trying to explain myself any more.

                                     -- Adam




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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  1:05           ` Adam Beneschan
@ 2010-02-12  2:35             ` Hibou57 (Yannick Duchêne)
  2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
                                 ` (5 more replies)
  0 siblings, 6 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  2:35 UTC (permalink / raw)


On 12 fév, 02:05, Adam Beneschan <a...@irvine.com> wrote:
> Hope this clears things up.  If instead I've just created more
> confusion, I apologize and promise to refrain from making things worse
> by trying to explain myself any more.
>
>                                      -- Adam

You're joking, aren't you ? You did not really though this words ...

Well, the story continues. First of all, I apologize to not have read
all comments so far (not entirely), which will be done whatever.

Here is a second test I've drove, to be really sure about what's going
on.
Here is the plan : start from a simple case, and follow a path to a
similar case to the one which gave the doubts exposed in the initial
post of this thread.

This comes into six simple samples, A to F. Simplified on purpose to
ease quick overview (no more explicit spy, add it yourself if you want
to the check what's asserted).

A single comment in each heading explain the difference of one test
compared to its predecessor, as well the observation made (which I
made with a spy which is dropped from this samples, for the reason
given above). The trouble occurs at step F.

I will post each samples on its own post, to ease quoting (hope this
sequence of six posts will not be too much annoying).

Here we go ...



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  2:35             ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
  2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
                                 ` (4 subsequent siblings)
  5 siblings, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  2:36 UTC (permalink / raw)


procedure A is
   -- Defines a limited type returned by a function.
   -- Observations : Entity is initialized when it is
   -- created an New_Limited, and finalized when its
   -- scope (that is, A) is terminated.
   -- Conclusion : everything's fine.

   package P is
      type Limited_Type is limited null record;
      function New_Limited return Limited_Type;
   end P;

   package body P is
      function New_Limited return Limited_Type is
      begin
         return R : Limited_Type do
            null;
         end return;
      end;
   end P;

   Entity : P.Limited_Type := P.New_Limited;

begin
   null;
end A;



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  2:35             ` Hibou57 (Yannick Duchêne)
  2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
  2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
                                 ` (3 subsequent siblings)
  5 siblings, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  2:36 UTC (permalink / raw)


procedure B is
   -- Variation from A : New_Limited now
   -- relies on an intermediate function,
   -- Pre_New_Limited.
   -- Observations : still fine.

   package P is
      type Limited_Type is limited null record;
      function New_Limited return Limited_Type;
   end P;

   package body P is
      function Pre_New_Limited return Limited_Type is
      begin
         return R : Limited_Type do
            null;
         end return;
      end;

      function New_Limited return Limited_Type is
      begin
         return R : Limited_Type := Pre_New_Limited do
            null;
         end return;
      end;
   end P;

   Entity : P.Limited_Type := P.New_Limited;

begin
   null;
end B;



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  2:35             ` Hibou57 (Yannick Duchêne)
  2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
  2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
  2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
                                 ` (2 subsequent siblings)
  5 siblings, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  2:36 UTC (permalink / raw)


procedure C is
   -- Variation from B : the Limited_Type
   -- is now made tagged limited (instead
   -- of just limited as so far).
   -- Observations : still OK.

   package P is
      type Limited_Type is tagged limited null record;
      function New_Limited return Limited_Type;
   end P;

   package body P is
      function Pre_New_Limited return Limited_Type is
      begin
         return R : Limited_Type do
            null;
         end return;
      end;

      function New_Limited return Limited_Type is
      begin
         return R : Limited_Type := Pre_New_Limited do
            null;
         end return;
      end;
   end P;

   Entity : P.Limited_Type := P.New_Limited;

begin
   null;
end C;



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  2:35             ` Hibou57 (Yannick Duchêne)
                                 ` (2 preceding siblings ...)
  2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
  2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
  2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
  5 siblings, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  2:37 UTC (permalink / raw)


procedure D is
   -- Variation from C : the returned type
   -- is now a derived type.
   -- Observations : all is nice (be patient,
   -- troubles will comes soon enough).

   package P is
      type Limited_Type is tagged limited null record;
      subtype Limited_Class is Limited_Type'Class;
      function New_Limited return Limited_Class;
   end P;

   package body P is
      type Derived_Limited_Type is
         new Limited_Type with null record;

      function New_Derived return Derived_Limited_Type is
      begin
         return R : Derived_Limited_Type do
            null;
         end return;
      end;

      function New_Limited return Limited_Class is
      begin
         return R : Limited_Class := New_Derived do
            null;
         end return;
      end;
   end P;

   Entity : P.Limited_Class := P.New_Limited;

begin
   null;
end D;



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  2:35             ` Hibou57 (Yannick Duchêne)
                                 ` (3 preceding siblings ...)
  2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
  2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
  5 siblings, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  2:37 UTC (permalink / raw)


procedure E is
   -- Variation from D : Limited_Type is
   -- now made a limited interface (instead
   -- of a limited tagged) and the
   -- derived type is made limited too
   -- Note : although the interface is limited,
   -- the derived type will not be automatically
   -- limited if this was not explicitly
   -- specify.
   -- Observations : mmmh... that's good
   -- (but not for long : have look at F).

   package P is
      type Limited_Type is limited interface;
      subtype Limited_Class is Limited_Type'Class;
      function New_Limited return Limited_Class;
   end P;

   package body P is
      type Derived_Limited_Type is limited
         new Limited_Type with null record;

      function New_Derived return Derived_Limited_Type is
      begin
         return R : Derived_Limited_Type do
            null;
         end return;
      end;

      function New_Limited return Limited_Class is
      begin
         return R : Limited_Class := New_Derived do
            null;
         end return;
      end;
   end P;

   Entity : P.Limited_Class := P.New_Limited;

begin
   null;
end E;



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  2:35             ` Hibou57 (Yannick Duchêne)
                                 ` (4 preceding siblings ...)
  2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
  2010-02-12  4:27                 ` Hibou57 (Yannick Duchêne)
  5 siblings, 1 reply; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  2:37 UTC (permalink / raw)


procedure F is
   -- Variation from E : the derived
   -- limited type is now made a protected
   -- type (which is still limited, implicitly).
   -- Observations : Arghh! Finalzation occurs
   -- right after Initialization.
   -- Conclusion : so fat, every thing was
   -- working as expected, but breaks as
   -- soon as the derived limited type
   -- is made a protected type.
   -- Should there be a different handling
   -- of Initialization and Finalization when
   -- the type is a protected type instead of
   -- simply a tagged limited type ? To be
   -- continued ...

   package P is
      type Limited_Type is limited interface;
      subtype Limited_Class is Limited_Type'Class;
      function New_Limited return Limited_Class;
   end P;

   package body P is
      protected type Derived_Limited_Type is
         new Limited_Type with end;

      protected body Derived_Limited_Type is end;

      function New_Derived return Derived_Limited_Type is
      begin
         return R : Derived_Limited_Type do
            null;
         end return;
      end;

      function New_Limited return Limited_Class is
      begin
         return R: Limited_Class := New_Derived do
            null;
         end return;
      end;
   end P;

   Entity : P.Limited_Class := P.New_Limited;

begin
   null;
end F;



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  4:27                 ` Hibou57 (Yannick Duchêne)
  2010-02-12  4:28                   ` Hibou57 (Yannick Duchêne)
  0 siblings, 1 reply; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  4:27 UTC (permalink / raw)


Back here (I was busy at some intermediate things).

It seems to me, there is indeed a GNAT bug here, as this next sample
which solve the trouble shows. With G, initialization and finalization
are done just like I was expecting.

procedure G is
   -- Variation from G : the protected
   -- type is wrapped in a limited record
   -- which is handle the derivation of
   -- the Limited_Type.
   -- Observations : Entity is initialized
   -- and Finalized as expected (like in A),
   -- and its component of Protected_Type is
   -- initialized before Entity is Initialized
   -- (as expected) and Finalized after
   -- Entity is Finalized (also as expected).
   -- It seems to me (unless there are contradictory
   -- interpretation of these observations), that
   -- a bug is confirmed here, and the construct
   -- provided here is a possible workaround.

   package P is
      type Limited_Type is limited interface;
      subtype Limited_Class is Limited_Type'Class;
      function New_Limited return Limited_Class;
   end P;

   package body P is
      protected type Protected_Type is end;

      protected body Protected_Type is end;

      type Derived_Limited_Type is
         limited new Limited_Type with
      record
         Wrapped_Protected_Item : Protected_Type;
      end record;

      function New_Derived return Derived_Limited_Type is
      begin
         return R : Derived_Limited_Type do
            null;
         end return;
      end;

      function New_Limited return Limited_Class is
      begin
         return R: Limited_Class := New_Derived do
            null;
         end return;
      end;
   end P;

   Entity : P.Limited_Class := P.New_Limited;

begin
   null;
end G;



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  4:27                 ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  4:28                   ` Hibou57 (Yannick Duchêne)
  0 siblings, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  4:28 UTC (permalink / raw)


Tipo error :

Read

procedure G is
   -- Variation from F : the protected
   -- type is wrapped in a limited record
   -- which handles the derivation of
   -- the Limited_Type.

Instead of

procedure G is
   -- Variation from G : the protected
   -- type is wrapped in a limited record
   -- which is handle the derivation of
   -- the Limited_Type.



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 15:16 ` Robert A Duff
  2010-02-11 17:40   ` Adam Beneschan
@ 2010-02-12  4:40   ` Hibou57 (Yannick Duchêne)
  1 sibling, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  4:40 UTC (permalink / raw)


On 11 fév, 16:16, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
> I'm not going to read your code carefully, but that doesn't
> seem right.  If you have:
>
>     X : T := F(...);
>
> the result of F is "built in place" in X, and should be finalized
> when the procedure containing X is left.
the result of F is "built in place" in X : Yes, that's what I was
expecting too !
And should be finalized when the procedure containing X is left : the
same !
So you confirmed my expectations.
Try the Test program, and you will see this things are not going this
way with it.
Things works nice with G.



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 17:40   ` Adam Beneschan
  2010-02-11 19:10     ` Robert A Duff
  2010-02-12  0:44     ` Randy Brukardt
@ 2010-02-12  4:47     ` Hibou57 (Yannick Duchêne)
  2010-02-12 18:02       ` Adam Beneschan
  2010-02-12  4:49     ` Hibou57 (Yannick Duchêne)
  3 siblings, 1 reply; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  4:47 UTC (permalink / raw)


On 11 fév, 18:40, Adam Beneschan <a...@irvine.com> wrote:
> Yes, I believe that's right, and it's spelled out clearly in the RM,
> in sections 7.6(17.1/3-17.11/3 and especially 17.7/3), 6.5(5.8/3),
> 6.5(23/2), 7.6(4), and 3.10.2(10.1/2).
With the exception of 6.5(23/2), none of these references exists in my
annotated RM. Was this a joke ?




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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 17:40   ` Adam Beneschan
                       ` (2 preceding siblings ...)
  2010-02-12  4:47     ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  4:49     ` Hibou57 (Yannick Duchêne)
  3 siblings, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  4:49 UTC (permalink / raw)


On 11 fév, 18:40, Adam Beneschan <a...@irvine.com> wrote:
> But more simply, as I understand it: (1) When you have an extended
> return, the return object is used as the anonymous object that holds
> the function result at the point of the function call, so it's not
> finalized until the caller is done with the anonymous object; and (2)
> when the object is built in place, the anonymous object "mutates into"
> the new object and is not finalized (7.6(17.7/3)).  So yes, no
> finalization should be done until X goes out of scope.
>
>                                      -- Adam


So yes, no finalization should be done until X goes out of scope :
second confirmation.



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 21:51       ` Adam Beneschan
  2010-02-11 22:49         ` Hibou57 (Yannick Duchêne)
  2010-02-11 22:53         ` Robert A Duff
@ 2010-02-12  5:25         ` Hibou57 (Yannick Duchêne)
  2010-02-12  9:27         ` Alex R. Mosteo
  3 siblings, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  5:25 UTC (permalink / raw)


On 11 fév, 22:51, Adam Beneschan <a...@irvine.com> wrote:
> point of the nasty language in 3.10.2(10.1).  Which is another way of

[ARM 3.10.2(10.1/2)]
> Within a return statement, the accessibility level of the return
> object is that of the execution of the return statement. If the
> return statement completes normally by returning from the function,
> then prior to leaving the function, the accessibility level of the
> return object changes to be a level determined by the point of call,
> as does the level of any coextensions (see below) of the return
> object.

I don't feel it's so nasty (seems logic and coherent to me). But it's
about “ Operations of Access Types ” (3.10.2), not limited type (while
there are some similarities in some way).



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 23:08             ` Robert A Duff
  2010-02-11 23:18               ` Hibou57 (Yannick Duchêne)
  2010-02-12  0:48               ` Randy Brukardt
@ 2010-02-12  5:37               ` Hibou57 (Yannick Duchêne)
  2010-02-13  1:54                 ` Randy Brukardt
  2010-02-12  5:39               ` Hibou57 (Yannick Duchêne)
  3 siblings, 1 reply; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  5:37 UTC (permalink / raw)


On 12 fév, 00:08, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
> Extended return statements are important in the limited case,
> because you often want to say something like "Result.X := ...;".
> And as you discovered, aggregates aren't allowed for protected
> or task types (which was probably a language design mistake).
I agree with this in some way, as protected are largely handled like
records. Further more, when you've made a syntactic while writing the
declaration or the body of a protected, then GNAT, most of times
points the error using the term "record" in the message (by the way,
with respect to the way the language is defined, I feel this kind of
message is not well suited, these may be disturbing for some users).

On the other hand, why would someone want to initialize any thing in a
protected ? The private part being only visible to the protected it-
self, this would not make sense. Well, sure it would be useful to
return a protected where a class-wide type is expected as the return
result : the language requires an initialization here, thus the idea
of an aggregate for protected and task in this purpose, in order to be
able to initialize this class-wide type. But this should be an empty
aggregate. What is needed, is not really an aggregate, but something
to initialize an entity of class-wide type.

Better than an aggregate for protected and task, there should be
something acting like an empty aggregate, which would be to be used as
an initializer for protected and task only.



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 23:08             ` Robert A Duff
                                 ` (2 preceding siblings ...)
  2010-02-12  5:37               ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  5:39               ` Hibou57 (Yannick Duchêne)
  2010-02-12 15:10                 ` Robert A Duff
  3 siblings, 1 reply; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  5:39 UTC (permalink / raw)


On 12 fév, 00:08, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
> Extended return statements are not so important for nonlimited types,
> but they do come in handy in that case, too.
While this may be useful, if it was, to have a way to return none-
limited as built-in-place, for efficiency purpose (just suggesting
this be to investigated, I do not assert this could surely be done
like this and as-is).



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 23:24     ` Robert A Duff
@ 2010-02-12  5:41       ` Hibou57 (Yannick Duchêne)
  2010-02-12 15:15         ` Robert A Duff
  0 siblings, 1 reply; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12  5:41 UTC (permalink / raw)


On 12 fév, 00:24, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
> Well, I don't find it "graceful" that single-element positional
> aggregates are not allowed.  And zero-element ones.  I think
> it's just bad language design.
It seems you are suggesting the ambiguity should be resolved
semantically. Why not :)



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-11 21:51       ` Adam Beneschan
                           ` (2 preceding siblings ...)
  2010-02-12  5:25         ` Hibou57 (Yannick Duchêne)
@ 2010-02-12  9:27         ` Alex R. Mosteo
  2010-02-12 16:43           ` Adam Beneschan
  3 siblings, 1 reply; 65+ messages in thread
From: Alex R. Mosteo @ 2010-02-12  9:27 UTC (permalink / raw)


Adam Beneschan wrote:

> On Feb 11, 11:10 am, Robert A Duff <bobd...@shell01.TheWorld.com>
> wrote:
>> Adam Beneschan <a...@irvine.com> writes:
>> > But more simply, as I understand it: (1) When you have an extended
>> > return, the return object is used as the anonymous object that holds
>> > the function result at the point of the function call, so it's not
>> > finalized until the caller is done with the anonymous object; and (2)
>> > when the object is built in place, the anonymous object "mutates into"
>> > the new object and is not finalized (7.6(17.7/3)).  So yes, no
>> > finalization should be done until X goes out of scope.
>>
>> Just to be clear: There's nothing particularly special about
>> extended return statements, other than the fact that they
>> provide a name for the result.
> 
> That last is an important distinction, however.  A function call
> involves (conceptually) an anonymous object.  For a normal return (for
> a non-limited type):
> 
>    return Some_Expression;
> 
> Some_Expression is computed and then assigned into the anonymous
> object.  This assignment involves an Adjust.  Then, at some point,
> whatever objects went into creating Some_Expression will get finalized
> when the function exits.  If Some_Expression is a local variable, for
> instance, that variable will get finalized.  If some other temporary
> needs to be created in order to hold the value of Some_Expression,
> that temporary will be finalized.
> 
> For an extended return,
> 
>    return R : T;
> 
> R is not a local variable, and it isn't "assigned" into the anonymous
> object; thus, there's no Adjust, and R is not finalized when the
> function returns (but the anonymous object will be finalized later,
> except when it mutates into some other object).  I think that's the
> point of the nasty language in 3.10.2(10.1).  Which is another way of
> saying that R is a name for the result (as you said), not a distinct
> object that gets copied to the result.  I thought it would be helpful
> to point it out---not to you, but to other readers.  It's hardly a
> trivial difference, and it's an important one to understand when
> adjusts and finalizations are involved.  Anyway, I hope this helps
> someone.

I remember an old thread I started on return by reference. My question then 
was if gnat was clever enough to optimize away copies in returned values 
used as constants, specifically using the container library. The answer 
empirically found was that it wasn't.

While not the same thing as a C++ return by constant reference, if I 
interpret you correctly, this kind of return X : T; removes one copy of the 
object in the returning machinery, by using the destination as in-place 
receptacle, right? If so, I wonder if it's worth the attempt to use this in 
some speed critical code.



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  5:39               ` Hibou57 (Yannick Duchêne)
@ 2010-02-12 15:10                 ` Robert A Duff
  2010-02-12 17:15                   ` (Hibou57) Yannick Duchêne
  0 siblings, 1 reply; 65+ messages in thread
From: Robert A Duff @ 2010-02-12 15:10 UTC (permalink / raw)


"Hibou57 (Yannick Duch�ne)" <yannick_duchene@yahoo.fr> writes:

> On 12 f�v, 00:08, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
>> Extended return statements are not so important for nonlimited types,
>> but they do come in handy in that case, too.
> While this may be useful, if it was, to have a way to return none-
> limited as built-in-place, for efficiency purpose (just suggesting
> this be to investigated, I do not assert this could surely be done
> like this and as-is).

Again, extended returns do NOT cause build-in-place.
For non-limited, the compiler may choose build-in-place
for efficiency in some cases.

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  5:41       ` Hibou57 (Yannick Duchêne)
@ 2010-02-12 15:15         ` Robert A Duff
  2010-02-12 16:27           ` Jean-Pierre Rosen
                             ` (2 more replies)
  0 siblings, 3 replies; 65+ messages in thread
From: Robert A Duff @ 2010-02-12 15:15 UTC (permalink / raw)


"Hibou57 (Yannick Duch�ne)" <yannick_duchene@yahoo.fr> writes:

> On 12 f�v, 00:24, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
>> Well, I don't find it "graceful" that single-element positional
>> aggregates are not allowed. �And zero-element ones. �I think
>> it's just bad language design.
> It seems you are suggesting the ambiguity should be resolved
> semantically. Why not :)

No, it should be syntactic.  And it should be more obvious
than counting the number of expressions between "(" and ")".

Aggregates should use "[" and "]", so there's no confusion.
An empty aggregate would be "[ ]", and a singleton
would be "[X]".  As far as I know, the only reason
this wasn't done was because of keyboards/character sets
that didn't have those characters.  But that's a bogus
reason -- it could be done just like the stuff in J.2.

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a  function
  2010-02-12 15:15         ` Robert A Duff
@ 2010-02-12 16:27           ` Jean-Pierre Rosen
  2010-02-12 17:53             ` Jacob Sparre Andersen
  2010-02-13  1:59             ` Randy Brukardt
  2010-02-12 16:57           ` Adam Beneschan
  2010-02-13  9:54           ` Dmitry A. Kazakov
  2 siblings, 2 replies; 65+ messages in thread
From: Jean-Pierre Rosen @ 2010-02-12 16:27 UTC (permalink / raw)


Robert A Duff a �crit :
 > Aggregates should use "[" and "]", so there's no confusion.
> An empty aggregate would be "[ ]", and a singleton
> would be "[X]".  As far as I know, the only reason
> this wasn't done was because of keyboards/character sets
> that didn't have those characters.  But that's a bogus
> reason -- it could be done just like the stuff in J.2.
> 
It shows your age when you think you started programming on a TTY-33...


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



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  9:27         ` Alex R. Mosteo
@ 2010-02-12 16:43           ` Adam Beneschan
  2010-02-12 19:11             ` Robert A Duff
  0 siblings, 1 reply; 65+ messages in thread
From: Adam Beneschan @ 2010-02-12 16:43 UTC (permalink / raw)


On Feb 12, 1:27 am, "Alex R. Mosteo" <alejan...@mosteo.com> wrote:

> I remember an old thread I started on return by reference. My question then
> was if gnat was clever enough to optimize away copies in returned values
> used as constants, specifically using the container library. The answer
> empirically found was that it wasn't.
>
> While not the same thing as a C++ return by constant reference, if I
> interpret you correctly, this kind of return X : T; removes one copy of the
> object in the returning machinery, by using the destination as in-place
> receptacle, right? If so, I wonder if it's worth the attempt to use this in
> some speed critical code.

Maybe.  Doing it this way could remove one copy, according to the
language semantics.  However, the compiler can of course generate any
code it wants, if it has the effect that the language semantics
demand.

I did try this with one compiler:

   function Func1 return Rec is
      Result : Rec;
   begin
      Result.Component1 := <blahblah>;
      Result.Component2 := <blahblah>;
      return Result;
   end;

   function Func2 return Rec is
   begin
      return Result : Rec do
         Result.Component1 := <blahblah>;
         Result.Component2 := <blahblah>;
      end return;
   end Func2;

With optimization turned off, Func2 did generate one less copy.
However, the generated code passed the address of a "result object" as
a parameter to the functions, and this means Func2 would be using
indirection through this address to set the components, while Func1
would be setting them on the local stack frame.  Whether this
indirection adds any cycles, I don't know.  I'd guess that it
wouldn't, but this could depend on the processor.

But, assuming that there are no controlled components, there's nothing
preventing the compiler from generating the same code for Func1 as for
Func2, and eliminating the extra copy.  So I guess that using extended
return might be worth a try---try it both ways, and see if the
compiler generates faster code.

If there are controlled components, then the semantics are different,
because Func1 will have to assign Result to the "result
object" (requiring an "adjust" operation) and then finalize Result
(requiring a "finalize" operation).  The language gives compilers
permission to remove adjust/finalize pairs in some cases, but I don't
know if this is one of those cases.  If not, then this is a case where
extended return will definitely benefit you.

                                 -- Adam






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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 15:15         ` Robert A Duff
  2010-02-12 16:27           ` Jean-Pierre Rosen
@ 2010-02-12 16:57           ` Adam Beneschan
  2010-02-12 18:07             ` mockturtle
                               ` (2 more replies)
  2010-02-13  9:54           ` Dmitry A. Kazakov
  2 siblings, 3 replies; 65+ messages in thread
From: Adam Beneschan @ 2010-02-12 16:57 UTC (permalink / raw)


On Feb 12, 7:15 am, Robert A Duff <bobd...@shell01.TheWorld.com>
wrote:

> No, it should be syntactic.  And it should be more obvious
> than counting the number of expressions between "(" and ")".
>
> Aggregates should use "[" and "]", so there's no confusion.
> An empty aggregate would be "[ ]", and a singleton
> would be "[X]".  As far as I know, the only reason
> this wasn't done was because of keyboards/character sets
> that didn't have those characters.  But that's a bogus
> reason -- it could be done just like the stuff in J.2.

I thought it was because of keypunch machines!  Yes, there were still
a few of those around when Ada was first designed.

I also remember some of the attempted rationalizations at the time; in
particular, why did Ada use parentheses for both subprogram calls and
array indexing, when other popular languages (Pascal and C) used
square brackets for indexing.  Someone came up with an argument that
it was actually a good thing to use the same characters for both,
because then if your program uses Arr(Index), where Arr is an array,
you could redesign your program to make "Arr" a function and the
change would be transparent.  That seemed like a stretch at the time.

Now that the language requires compilers to allow identifiers
containing any character in any alphabet that exists or has ever
existed, including ancient languages like Ogham (http://
en.wikipedia.org/wiki/Ogham --- seriously, I'm dying to use an
Eamhancholl in one of my variable names), there doesn't seem to be
much justification for avoiding square and curly brackets, besides
inertia.  No, you don't want use so many special characters that your
program starts to look like Egyptial hieroglyphics---or worse, a C++
program---but I do think that allowing the sort of syntax you suggest
for aggregates would be a plus.

                                    -- Adam




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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 15:10                 ` Robert A Duff
@ 2010-02-12 17:15                   ` (Hibou57) Yannick Duchêne
  2010-02-12 19:07                     ` Robert A Duff
  0 siblings, 1 reply; 65+ messages in thread
From: (Hibou57) Yannick Duchêne @ 2010-02-12 17:15 UTC (permalink / raw)


Le Fri, 12 Feb 2010 16:10:19 +0100, Robert A Duff  
<bobduff@shell01.theworld.com> a écrit:
>>> Extended return statements are not so important for nonlimited types,
>>> but they do come in handy in that case, too.
>> While this may be useful, if it was, to have a way to return none-
>> limited as built-in-place, for efficiency purpose (just suggesting
>> this be to investigated, I do not assert this could surely be done
>> like this and as-is).
>
> Again, extended returns do NOT cause build-in-place.
> For non-limited, the compiler may choose build-in-place
> for efficiency in some cases.
>
> - Bob
It was a suggestion (you seems to really be afraid of this possible  
confusion)

-- 
Test



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 16:27           ` Jean-Pierre Rosen
@ 2010-02-12 17:53             ` Jacob Sparre Andersen
  2010-02-12 18:05               ` Adam Beneschan
  2010-02-13  1:59             ` Randy Brukardt
  1 sibling, 1 reply; 65+ messages in thread
From: Jacob Sparre Andersen @ 2010-02-12 17:53 UTC (permalink / raw)


Jean-Pierre Rosen ha scritto:

> It shows your age when you think you started programming on a
> TTY-33...

I may be a bit younger.  I think I started programming on a VT-220...

Cheers,

Jacob
-- 
"The current state of knowledge can be summarised thus:
 In the beginning, there was nothing, which exploded."




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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  4:47     ` Hibou57 (Yannick Duchêne)
@ 2010-02-12 18:02       ` Adam Beneschan
  0 siblings, 0 replies; 65+ messages in thread
From: Adam Beneschan @ 2010-02-12 18:02 UTC (permalink / raw)


On Feb 11, 8:47 pm, Hibou57 (Yannick Duchêne)
<yannick_duch...@yahoo.fr> wrote:
> On 11 fév, 18:40, Adam Beneschan <a...@irvine.com> wrote:> Yes, I believe that's right, and it's spelled out clearly in the RM,
> > in sections 7.6(17.1/3-17.11/3 and especially 17.7/3), 6.5(5.8/3),
> > 6.5(23/2), 7.6(4), and 3.10.2(10.1/2).
>
> With the exception of 6.5(23/2), none of these references exists in my
> annotated RM. Was this a joke ?

No.  And it looks like you found 3.10.2(10.1/2) since you mentioned it
in a later post.  Some of the others are in Ada 2005 R2 (the part
about result objects "mutating into" other objects was added after the
original version of Ada 2005).  If you're having problems locating
sections, let me know---it's possible I made a typo.

The "spelled out clearly" was a joke, though.  In particular, my
repeated attempts to understand the accessibility rules in 3.10.2 have
contributed to the big profits enjoyed by the manufacturers of Advil
and similar drugs.  (OK, it's a very tiny contribution, but still
greater than zero.)

                            -- Adam







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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 17:53             ` Jacob Sparre Andersen
@ 2010-02-12 18:05               ` Adam Beneschan
  0 siblings, 0 replies; 65+ messages in thread
From: Adam Beneschan @ 2010-02-12 18:05 UTC (permalink / raw)


On Feb 12, 9:53 am, Jacob Sparre Andersen <spa...@nbi.dk> wrote:
> Jean-Pierre Rosen ha scritto:
>
> > It shows your age when you think you started programming on a
> > TTY-33...
>
> I may be a bit younger.  I think I started programming on a VT-220...

Yeah, one of them durn newfangled cathode ray tube things.  You
youngsters have no idea how good you have it.  I had to walk five
miles to the computing center, uphill both ways, with one of them big
old keypunch machines strapped to my back.

                          -- Adam



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 16:57           ` Adam Beneschan
@ 2010-02-12 18:07             ` mockturtle
  2010-02-12 18:29               ` Hibou57 (Yannick Duchêne)
  2010-02-12 19:09             ` Robert A Duff
  2010-02-12 19:10             ` (see below)
  2 siblings, 1 reply; 65+ messages in thread
From: mockturtle @ 2010-02-12 18:07 UTC (permalink / raw)


On Feb 12, 5:57 pm, Adam Beneschan <a...@irvine.com> wrote:
>
> Now that the language requires compilers to allow identifiers
> containing any character in any alphabet that exists or has ever
> existed, including ancient languages like Ogham (http://
> en.wikipedia.org/wiki/Ogham --- seriously, I'm dying to use an
> Eamhancholl in one of my variable names),

To increase readibility, right? :-)) (sorry, I could not resist)




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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 18:07             ` mockturtle
@ 2010-02-12 18:29               ` Hibou57 (Yannick Duchêne)
  0 siblings, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-12 18:29 UTC (permalink / raw)


Le Fri, 12 Feb 2010 19:07:43 +0100, mockturtle <framefritti@gmail.com> a  
écrit:

> On Feb 12, 5:57 pm, Adam Beneschan <a...@irvine.com> wrote:
>>
>> Now that the language requires compilers to allow identifiers
>> containing any character in any alphabet that exists or has ever
>> existed, including ancient languages like Ogham (http://
>> en.wikipedia.org/wiki/Ogham --- seriously, I'm dying to use an
>> Eamhancholl in one of my variable names),
>
> To increase readibility, right? :-)) (sorry, I could not resist)
>
OT: seems the Celts heavily normalized the hash sign 3000 years before the  
ASCII does

-- 
This isn't an oops



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 17:15                   ` (Hibou57) Yannick Duchêne
@ 2010-02-12 19:07                     ` Robert A Duff
  0 siblings, 0 replies; 65+ messages in thread
From: Robert A Duff @ 2010-02-12 19:07 UTC (permalink / raw)


"(Hibou57) Yannick Duch�ne" <yannick_duchene@yahoo.fr> writes:

> Le Fri, 12 Feb 2010 16:10:19 +0100, Robert A Duff
> <bobduff@shell01.theworld.com> a �crit:
>>>> Extended return statements are not so important for nonlimited types,
>>>> but they do come in handy in that case, too.
>>> While this may be useful, if it was, to have a way to return none-
>>> limited as built-in-place, for efficiency purpose (just suggesting
>>> this be to investigated, I do not assert this could surely be done
>>> like this and as-is).
>>
>> Again, extended returns do NOT cause build-in-place.
>> For non-limited, the compiler may choose build-in-place
>> for efficiency in some cases.
>>
>> - Bob
> It was a suggestion...

You mean a suggestion for the language,
or a suggestion for a compiler optimization?

If the latter, well, I think the compiler ought
to do the optimization whether or not the code
uses extended return.

>...(you seems to really be afraid of this possible
> confusion)

Well, yeah, lots of people seem to think that
extended return does much more than it does.
I'm just trying to help avoid that confusion.  ;-)

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 16:57           ` Adam Beneschan
  2010-02-12 18:07             ` mockturtle
@ 2010-02-12 19:09             ` Robert A Duff
  2010-02-13  2:00               ` Randy Brukardt
  2010-02-12 19:10             ` (see below)
  2 siblings, 1 reply; 65+ messages in thread
From: Robert A Duff @ 2010-02-12 19:09 UTC (permalink / raw)


Adam Beneschan <adam@irvine.com> writes:

> I also remember some of the attempted rationalizations at the time; in
> particular, why did Ada use parentheses for both subprogram calls and
> array indexing, when other popular languages (Pascal and C) used
> square brackets for indexing.  Someone came up with an argument that
> it was actually a good thing to use the same characters for both,
> because then if your program uses Arr(Index), where Arr is an array,
> you could redesign your program to make "Arr" a function and the
> change would be transparent.  That seemed like a stretch at the time.

Well, this one makes a little more sense than the aggregate thing.
But it doesn't work if you say "Arr(Index) := ..."!

I have mixed feelings.

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 16:57           ` Adam Beneschan
  2010-02-12 18:07             ` mockturtle
  2010-02-12 19:09             ` Robert A Duff
@ 2010-02-12 19:10             ` (see below)
  2 siblings, 0 replies; 65+ messages in thread
From: (see below) @ 2010-02-12 19:10 UTC (permalink / raw)


On 12/02/2010 16:57, in article
9c2b5c56-7abf-4523-844d-b48447587402@w27g2000pre.googlegroups.com, "Adam
Beneschan" <adam@irvine.com> wrote:

> I also remember some of the attempted rationalizations at the time; in
> particular, why did Ada use parentheses for both subprogram calls and
> array indexing, when other popular languages (Pascal and C) used
> square brackets for indexing.  Someone came up with an argument that
> it was actually a good thing to use the same characters for both,
> because then if your program uses Arr(Index), where Arr is an array,
> you could redesign your program to make "Arr" a function and the
> change would be transparent.  That seemed like a stretch at the time.

Douglas T. Ross, the author of AED-0, was keen on the idea of "uniform
referent" notation, i.e., using the form F(X) for a function call, an array
element, or the field F of record X (as in Algol W).

I think it had some merit, although much diminished by the invention of
opaque/private types.

-- 
Bill Findlay
<surname><forename> chez blueyonder.co.uk





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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 16:43           ` Adam Beneschan
@ 2010-02-12 19:11             ` Robert A Duff
  0 siblings, 0 replies; 65+ messages in thread
From: Robert A Duff @ 2010-02-12 19:11 UTC (permalink / raw)


Adam Beneschan <adam@irvine.com> writes:

> But, assuming that there are no controlled components, there's nothing
> preventing the compiler from generating the same code for Func1 as for
> Func2, and eliminating the extra copy.  So I guess that using extended
> return might be worth a try---try it both ways, and see if the
> compiler generates faster code.
>
> If there are controlled components, then the semantics are different,
> because Func1 will have to assign Result to the "result
> object" (requiring an "adjust" operation) and then finalize Result
> (requiring a "finalize" operation).  The language gives compilers
> permission to remove adjust/finalize pairs in some cases, but I don't
> know if this is one of those cases.

I think it is.  But I'm too lazy to look it up right now.

If I'm right, then compilers can optimize in both
controlled and non-controlled cases (for nonlimited
types).

>...If not, then this is a case where
> extended return will definitely benefit you.

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12  5:37               ` Hibou57 (Yannick Duchêne)
@ 2010-02-13  1:54                 ` Randy Brukardt
  0 siblings, 0 replies; 65+ messages in thread
From: Randy Brukardt @ 2010-02-13  1:54 UTC (permalink / raw)


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

"Hibou57 (Yannick Duch�ne)" <yannick_duchene@yahoo.fr> wrote in message 
news:8a8514af-0d80-4acc-a2de-d7128c345d97@b7g2000yqd.googlegroups.com...
...
>Better than an aggregate for protected and task, there should be
>something acting like an empty aggregate, which would be to be used as
>an initializer for protected and task only.

Right. That's what we were trying to do for Ada 2005, and it just didn't 
work out. It's weird that you can default initialize a component in an 
aggregate with <>, but there is no way to do that for an entire object. We 
also wanted to be able to default initialize the private part of an 
extension. But we ran into all kinds of weird problems. I don't plan to go 
there again myself, there were enough people who didn't like anything 
involving "others".

                                Randy.





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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 16:27           ` Jean-Pierre Rosen
  2010-02-12 17:53             ` Jacob Sparre Andersen
@ 2010-02-13  1:59             ` Randy Brukardt
  1 sibling, 0 replies; 65+ messages in thread
From: Randy Brukardt @ 2010-02-13  1:59 UTC (permalink / raw)


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

"Jean-Pierre Rosen" <rosen@adalog.fr> wrote in message 
news:2iv3lh.c8d.ln@hunter.axlog.fr...
> Robert A Duff a �crit :
> > Aggregates should use "[" and "]", so there's no confusion.
>> An empty aggregate would be "[ ]", and a singleton
>> would be "[X]".  As far as I know, the only reason
>> this wasn't done was because of keyboards/character sets
>> that didn't have those characters.  But that's a bogus
>> reason -- it could be done just like the stuff in J.2.
>>
> It shows your age when you think you started programming on a TTY-33...

That would have been an improvement. My freshman year at UW, my first real 
programming used Univac keypunches. They didn't even have lower case 
characters initially. But those were gone after a year or so; they 
introduced an ASCII compiler with a lot of fanfare (and incompatibility - 
characters took up 3 more bits).

                             Randy.





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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 19:09             ` Robert A Duff
@ 2010-02-13  2:00               ` Randy Brukardt
  2010-02-13  2:51                 ` Hibou57 (Yannick Duchêne)
  0 siblings, 1 reply; 65+ messages in thread
From: Randy Brukardt @ 2010-02-13  2:00 UTC (permalink / raw)


"Robert A Duff" <bobduff@shell01.TheWorld.com> wrote in message 
news:wccocjue0e7.fsf@shell01.TheWorld.com...
> Adam Beneschan <adam@irvine.com> writes:
>
>> I also remember some of the attempted rationalizations at the time; in
>> particular, why did Ada use parentheses for both subprogram calls and
>> array indexing, when other popular languages (Pascal and C) used
>> square brackets for indexing.  Someone came up with an argument that
>> it was actually a good thing to use the same characters for both,
>> because then if your program uses Arr(Index), where Arr is an array,
>> you could redesign your program to make "Arr" a function and the
>> change would be transparent.  That seemed like a stretch at the time.
>
> Well, this one makes a little more sense than the aggregate thing.
> But it doesn't work if you say "Arr(Index) := ..."!

Unless Tucker's latest project works out. Stay tuned...

                      Randy.





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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-13  2:00               ` Randy Brukardt
@ 2010-02-13  2:51                 ` Hibou57 (Yannick Duchêne)
  2010-02-13 15:59                   ` Robert A Duff
  0 siblings, 1 reply; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-13  2:51 UTC (permalink / raw)


Le Sat, 13 Feb 2010 03:00:55 +0100, Randy Brukardt <randy@rrsoftware.com>  
a écrit:
>> Well, this one makes a little more sense than the aggregate thing.
>> But it doesn't work if you say "Arr(Index) := ..."!
>
> Unless Tucker's latest project works out. Stay tuned...
What's the new Professor Sir Tucker Taft's project ?

-- 
No-no, this isn't an oops ...or I hope (TM) - Don't blame me... I'm just  
not lucky



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-12 15:15         ` Robert A Duff
  2010-02-12 16:27           ` Jean-Pierre Rosen
  2010-02-12 16:57           ` Adam Beneschan
@ 2010-02-13  9:54           ` Dmitry A. Kazakov
  2010-02-13 15:52             ` (see below)
  2010-02-13 15:53             ` Robert A Duff
  2 siblings, 2 replies; 65+ messages in thread
From: Dmitry A. Kazakov @ 2010-02-13  9:54 UTC (permalink / raw)


On Fri, 12 Feb 2010 10:15:17 -0500, Robert A Duff wrote:

> "Hibou57 (Yannick Duch�ne)" <yannick_duchene@yahoo.fr> writes:
> 
>> On 12 f�v, 00:24, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
>>> Well, I don't find it "graceful" that single-element positional
>>> aggregates are not allowed. �And zero-element ones. �I think
>>> it's just bad language design.
>> It seems you are suggesting the ambiguity should be resolved
>> semantically. Why not :)
> 
> No, it should be syntactic.  And it should be more obvious
> than counting the number of expressions between "(" and ")".
> 
> Aggregates should use "[" and "]", so there's no confusion.

Nope, the mathematical notation for a tuple is as in Ada (a,b,c,...), so
should it be. I see no problem in having it ambiguous (overloaded).

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



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-13  9:54           ` Dmitry A. Kazakov
@ 2010-02-13 15:52             ` (see below)
  2010-02-14 10:23               ` Dmitry A. Kazakov
  2010-02-13 15:53             ` Robert A Duff
  1 sibling, 1 reply; 65+ messages in thread
From: (see below) @ 2010-02-13 15:52 UTC (permalink / raw)


On 13/02/2010 09:54, in article jk97b2c81itt$.1h9s6uejsnxcu.dlg@40tude.net,
"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> wrote:

> On Fri, 12 Feb 2010 10:15:17 -0500, Robert A Duff wrote:
> 
>> "Hibou57 (Yannick Duch�ne)" <yannick_duchene@yahoo.fr> writes:
>> 
>>> On 12 f�v, 00:24, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
>>>> Well, I don't find it "graceful" that single-element positional
>>>> aggregates are not allowed. �And zero-element ones. �I think
>>>> it's just bad language design.
>>> It seems you are suggesting the ambiguity should be resolved
>>> semantically. Why not :)
>> 
>> No, it should be syntactic.  And it should be more obvious
>> than counting the number of expressions between "(" and ")".
>> 
>> Aggregates should use "[" and "]", so there's no confusion.
> 
> Nope, the mathematical notation for a tuple is as in Ada (a,b,c,...), so
> should it be. I see no problem in having it ambiguous (overloaded).

<a,b,c, ...>, surely?

-- 
Bill Findlay
<surname><forename> chez blueyonder.co.uk





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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-13  9:54           ` Dmitry A. Kazakov
  2010-02-13 15:52             ` (see below)
@ 2010-02-13 15:53             ` Robert A Duff
  2010-02-14 10:59               ` Dmitry A. Kazakov
  1 sibling, 1 reply; 65+ messages in thread
From: Robert A Duff @ 2010-02-13 15:53 UTC (permalink / raw)


"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

> Nope, the mathematical notation for a tuple is as in Ada (a,b,c,...), so
> should it be.

Well, none of the following Ada operators use the standard maths
notation:

    -  *  /  **  <=  >=  /=  and  or  not

And named notation:

    Date'(Year => 2010, Month => February, Day => 1)

is not standard maths notation -- it's superior to maths
notation.  In general, I find Ada programs much easier
to read that math textbooks, so I'm reluctant to borrow
too much from maths.

>... I see no problem in having it ambiguous (overloaded).

That's too much overloading, for my taste.

No big problem from an implementation point of view, though.

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-13  2:51                 ` Hibou57 (Yannick Duchêne)
@ 2010-02-13 15:59                   ` Robert A Duff
  2010-02-13 19:34                     ` Hibou57 (Yannick Duchêne)
  0 siblings, 1 reply; 65+ messages in thread
From: Robert A Duff @ 2010-02-13 15:59 UTC (permalink / raw)


"Hibou57 (Yannick Duch�ne)" <yannick_duchene@yahoo.fr> writes:

> What's the new Professor Sir Tucker Taft's project ?

The ARG is inventing some syntactic sugar to make user-defined
container code easier to read, and Tucker is doing most of
the work on that.  One example is that there will probably be some
mechanism to say:

    A(X) := A(X) + 1;

where A is (say) a hash table mapping strings to integers,
and X is a string.  User-defined array-indexing notation.

Also, some new kinds of for loops.  For example, looping
through the components of an array without any
horsing around with index values:

    for C : Character of My_String loop
        Do_Something(C);
    end loop;

The ": Character" above is optional, according to the latest proposal.

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-13 15:59                   ` Robert A Duff
@ 2010-02-13 19:34                     ` Hibou57 (Yannick Duchêne)
  2010-02-13 19:45                       ` Robert A Duff
  0 siblings, 1 reply; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-13 19:34 UTC (permalink / raw)


Le Sat, 13 Feb 2010 16:59:44 +0100, Robert A Duff  
<bobduff@shell01.theworld.com> a écrit:
>> What's the new Professor Sir Tucker Taft's project ?
>
> The ARG is inventing some syntactic sugar to make user-defined
> container code easier to read, and Tucker is doing most of
> the work on that.  One example is that there will probably be some
> mechanism to say:
>
>     A(X) := A(X) + 1;
>
> where A is (say) a hash table mapping strings to integers,
> and X is a string.  User-defined array-indexing notation.
>
> Also, some new kinds of for loops.  For example, looping
> through the components of an array without any
> horsing around with index values:
>
>     for C : Character of My_String loop
>         Do_Something(C);
>     end loop;
>
> The ": Character" above is optional, according to the latest proposal.
That's high-level language capability.

So that's to be added with the other project I've heard about here at  
comp.lang.ada, about first-class-functions (it was during the thread about  
making constant declarations overloadable if my mind is right) and the  
pre-post-condition discussed here and on fr.c.l.a.

As Santa Claus seems to be actually checking orders, do you know if there  
will be something like co-routines ? We already have tasks, but tasks are  
a bit too much heavy as co-routines. I was to open a thread to investigate  
this topic two weeks ago (I finally did not start it). I'm thinking about  
it, beside another topic about unknown discriminants.

-- 
No-no, this isn't an oops ...or I hope (TM) - Don't blame me... I'm just  
not lucky



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-13 19:34                     ` Hibou57 (Yannick Duchêne)
@ 2010-02-13 19:45                       ` Robert A Duff
  0 siblings, 0 replies; 65+ messages in thread
From: Robert A Duff @ 2010-02-13 19:45 UTC (permalink / raw)


"Hibou57 (Yannick Duch�ne)" <yannick_duchene@yahoo.fr> writes:

> So that's to be added with the other project I've heard about here at
> comp.lang.ada, about first-class-functions (it was during the thread
> about  making constant declarations overloadable if my mind is right)
> and the  pre-post-condition discussed here and on fr.c.l.a.
>
> As Santa Claus seems to be actually checking orders, do you know if
> there  will be something like co-routines ? We already have tasks, but
> tasks are  a bit too much heavy as co-routines.

No, probably not.  Probably no first-class functions, either.

- Bob



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-13 15:52             ` (see below)
@ 2010-02-14 10:23               ` Dmitry A. Kazakov
  0 siblings, 0 replies; 65+ messages in thread
From: Dmitry A. Kazakov @ 2010-02-14 10:23 UTC (permalink / raw)


On Sat, 13 Feb 2010 15:52:06 +0000, (see below) wrote:

> On 13/02/2010 09:54, in article jk97b2c81itt$.1h9s6uejsnxcu.dlg@40tude.net,
> "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> wrote:
> 
>> On Fri, 12 Feb 2010 10:15:17 -0500, Robert A Duff wrote:
>> 
>>> "Hibou57 (Yannick Duch�ne)" <yannick_duchene@yahoo.fr> writes:
>>> 
>>>> On 12 f�v, 00:24, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
>>>>> Well, I don't find it "graceful" that single-element positional
>>>>> aggregates are not allowed. �And zero-element ones. �I think
>>>>> it's just bad language design.
>>>> It seems you are suggesting the ambiguity should be resolved
>>>> semantically. Why not :)
>>> 
>>> No, it should be syntactic.  And it should be more obvious
>>> than counting the number of expressions between "(" and ")".
>>> 
>>> Aggregates should use "[" and "]", so there's no confusion.
>> 
>> Nope, the mathematical notation for a tuple is as in Ada (a,b,c,...), so
>> should it be. I see no problem in having it ambiguous (overloaded).
> 
> <a,b,c, ...>, surely?

Hmm, I am not sure if I ever saw that.

http://en.wikipedia.org/wiki/Tuple

BTW, if it were my choice, I would allow user-defined aggregates to take
any paired brackets (), [], {} and, maybe <>.

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



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-13 15:53             ` Robert A Duff
@ 2010-02-14 10:59               ` Dmitry A. Kazakov
  2010-02-14 22:00                 ` Hibou57 (Yannick Duchêne)
  0 siblings, 1 reply; 65+ messages in thread
From: Dmitry A. Kazakov @ 2010-02-14 10:59 UTC (permalink / raw)


On Sat, 13 Feb 2010 10:53:06 -0500, Robert A Duff wrote:

> "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:
> 
>> Nope, the mathematical notation for a tuple is as in Ada (a,b,c,...), so
>> should it be.
> 
> Well, none of the following Ada operators use the standard maths
> notation:
> 
>     -  *  /  **  <=  >=  /=  and  or  not

Hey, somebody pushed for Unicode in Ada2005. Isn't it time now to fix that?
(:-))

http://en.wikipedia.org/wiki/Unicode_mathematical_operators

> And named notation:
> 
>     Date'(Year => 2010, Month => February, Day => 1)
> 
> is not standard maths notation -- it's superior to maths
> notation.

I don't know if there is a math notation for date. But Date' prefix is
obviously offending.

BTW, ISO date notation is 2010-02-01. Here we go:

   type Month_Date is record
      Year  : Year_Number;
      Month : Month_Number;
   end record;

   function "-" (Year : Year_Number; Month : Month_Number)
      return Month_Date is
   begin
      return (Year, Month);
   end "-";

   function "-" (Left : Month_Date; Right : Day_Number) return Time is
   begin
      return Time_Of (Left.Year, Left.Month, Right);
   end "-";
   
   T : Time := 2010-02-01;

Isn't Ada great?

> In general, I find Ada programs much easier
> to read that math textbooks, so I'm reluctant to borrow
> too much from maths.

Agreed. But that depends on who writes the text/program. Mathematicians are
famous for being worst programmers ever. So I am not surprised that their
books are as unreadable as their programs. But it is the notation, which
allows to decipher at least something from that mess. It is 1000 years of
natural selection that brought this notation up. I remember reading some
ancient books on analysis and linear algebra when I was a student. They
were absolutely incomprehensive. They consistently avoided use of O() and
o(), wrote all limits in expanded, they do also all matrices (a11, a12, ...
a1N, a21, a22, ... ...) instead of just A etc. (:-))

>>... I see no problem in having it ambiguous (overloaded).
> 
> That's too much overloading, for my taste.

But keyed notation for a singleton is not only boring. It is
counterintuitive. There *nothing* to reorder there. It is just one element.
What does the index here? (Of course, we consider only the case where the
aggregate's length is known)

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



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

* Re: Initialization and Finalization of limited object "returned" by a function
  2010-02-14 10:59               ` Dmitry A. Kazakov
@ 2010-02-14 22:00                 ` Hibou57 (Yannick Duchêne)
  0 siblings, 0 replies; 65+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-14 22:00 UTC (permalink / raw)


Le Sun, 14 Feb 2010 11:59:44 +0100, Dmitry A. Kazakov  
<mailbox@dmitry-kazakov.de> a écrit:
>>> Nope, the mathematical notation for a tuple is as in Ada (a,b,c,...),  
>>> so
>>> should it be.
>>
>> Well, none of the following Ada operators use the standard maths
>> notation:
>>
>>     -  *  /  **  <=  >=  /=  and  or  not
>
> Hey, somebody pushed for Unicode in Ada2005. Isn't it time now to fix  
> that?
> (:-))
I use to think about this one , using the Unicode characters standing for  
this kind of relationship operator and others, but this would not work  
anyway in some editor/IDE, like GPS, and the ones looking like ASCII Art  
(the actual ones), are easier to input.

-- 
No-no, this isn't an oops ...or I hope (TM) - Don't blame me... I'm just  
not lucky



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

end of thread, other threads:[~2010-02-14 22:00 UTC | newest]

Thread overview: 65+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2010-02-11  4:37 Initialization and Finalization of limited object "returned" by a function Hibou57 (Yannick Duchêne)
2010-02-11  9:51 ` Hibou57 (Yannick Duchêne)
2010-02-11 11:00 ` Ludovic Brenta
2010-02-11 11:33   ` Jean-Pierre Rosen
2010-02-11 23:15   ` Hibou57 (Yannick Duchêne)
2010-02-11 23:24     ` Robert A Duff
2010-02-12  5:41       ` Hibou57 (Yannick Duchêne)
2010-02-12 15:15         ` Robert A Duff
2010-02-12 16:27           ` Jean-Pierre Rosen
2010-02-12 17:53             ` Jacob Sparre Andersen
2010-02-12 18:05               ` Adam Beneschan
2010-02-13  1:59             ` Randy Brukardt
2010-02-12 16:57           ` Adam Beneschan
2010-02-12 18:07             ` mockturtle
2010-02-12 18:29               ` Hibou57 (Yannick Duchêne)
2010-02-12 19:09             ` Robert A Duff
2010-02-13  2:00               ` Randy Brukardt
2010-02-13  2:51                 ` Hibou57 (Yannick Duchêne)
2010-02-13 15:59                   ` Robert A Duff
2010-02-13 19:34                     ` Hibou57 (Yannick Duchêne)
2010-02-13 19:45                       ` Robert A Duff
2010-02-12 19:10             ` (see below)
2010-02-13  9:54           ` Dmitry A. Kazakov
2010-02-13 15:52             ` (see below)
2010-02-14 10:23               ` Dmitry A. Kazakov
2010-02-13 15:53             ` Robert A Duff
2010-02-14 10:59               ` Dmitry A. Kazakov
2010-02-14 22:00                 ` Hibou57 (Yannick Duchêne)
2010-02-11 15:16 ` Robert A Duff
2010-02-11 17:40   ` Adam Beneschan
2010-02-11 19:10     ` Robert A Duff
2010-02-11 21:51       ` Adam Beneschan
2010-02-11 22:49         ` Hibou57 (Yannick Duchêne)
2010-02-11 22:53           ` Hibou57 (Yannick Duchêne)
2010-02-11 23:08             ` Robert A Duff
2010-02-11 23:18               ` Hibou57 (Yannick Duchêne)
2010-02-12  0:48               ` Randy Brukardt
2010-02-12  5:37               ` Hibou57 (Yannick Duchêne)
2010-02-13  1:54                 ` Randy Brukardt
2010-02-12  5:39               ` Hibou57 (Yannick Duchêne)
2010-02-12 15:10                 ` Robert A Duff
2010-02-12 17:15                   ` (Hibou57) Yannick Duchêne
2010-02-12 19:07                     ` Robert A Duff
2010-02-12  1:05           ` Adam Beneschan
2010-02-12  2:35             ` Hibou57 (Yannick Duchêne)
2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
2010-02-12  2:36               ` Hibou57 (Yannick Duchêne)
2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
2010-02-12  2:37               ` Hibou57 (Yannick Duchêne)
2010-02-12  4:27                 ` Hibou57 (Yannick Duchêne)
2010-02-12  4:28                   ` Hibou57 (Yannick Duchêne)
2010-02-11 22:53         ` Robert A Duff
2010-02-11 23:41           ` Adam Beneschan
2010-02-12  0:22             ` Robert A Duff
2010-02-12  5:25         ` Hibou57 (Yannick Duchêne)
2010-02-12  9:27         ` Alex R. Mosteo
2010-02-12 16:43           ` Adam Beneschan
2010-02-12 19:11             ` Robert A Duff
2010-02-12  0:44     ` Randy Brukardt
2010-02-12  4:47     ` Hibou57 (Yannick Duchêne)
2010-02-12 18:02       ` Adam Beneschan
2010-02-12  4:49     ` Hibou57 (Yannick Duchêne)
2010-02-12  4:40   ` Hibou57 (Yannick Duchêne)

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