comp.lang.ada
 help / color / mirror / Atom feed
* Calling a record type's methods (functions or procedure) when record is in an array
@ 2020-01-17 23:30 Mace Ayres
  2020-01-18 12:31 ` Simon Wright
                   ` (2 more replies)
  0 siblings, 3 replies; 12+ messages in thread
From: Mace Ayres @ 2020-01-17 23:30 UTC (permalink / raw)


My package 'trunks.ads' includes 
...
type a_trunk;.

function set_lock ...  return lock_state;

function post_val(v:integer) --- return integer
...
type a_trunk is
  record
     id : ,,,
    val
    ...
    lock  : lock_state    -- enumeration type defined earlier (open, locked)
  end record;

Package body 'trunks.adb  includes ...

function set_lock (  ..... not relevant

function post_val i(v:integer)  return integer is ..return v;

------
In package 1 I have a multi dimension array of type a_truck that I get to with
..
loop de loop i,j
my_trunk_array (i)(j)
..
-------

To modify the item val in the trunk at array (5)(3) I code..

... my_truck_arrary(5)(3).val := trunks.post_val(N)

rather than my_tunk_arrary(5)(3).val := N

so I don't directly access the a_trunk record's value fields directly

-- I have to add the private part too, to hide the inners of type a_trunk.

It seem a little convoluted, but I see no other way to manipulate my a_truck type records that only 'exist' the array.

I am just learning Ada. Is this reasonable?





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

* Re: Calling a record type's methods (functions or procedure) when record is in an array
  2020-01-17 23:30 Calling a record type's methods (functions or procedure) when record is in an array Mace Ayres
@ 2020-01-18 12:31 ` Simon Wright
  2020-01-18 18:02 ` Mace Ayres
  2020-01-19 15:06 ` Mace Ayres
  2 siblings, 0 replies; 12+ messages in thread
From: Simon Wright @ 2020-01-18 12:31 UTC (permalink / raw)


Mace Ayres <maceayres0@gmail.com> writes:

> To modify the item val in the trunk at array (5)(3) I code..
>
> ... my_truck_arrary(5)(3).val := trunks.post_val(N)
>
> rather than my_tunk_arrary(5)(3).val := N
>
> so I don't directly access the a_trunk record's value fields directly

? this code does indeed access the value fields directly!

> -- I have to add the private part too, to hide the inners of type
> a_trunk.

You're looking for an accessor (though accessors aren't always a good
idea; there might be checks needed, attributes may be related so you
need to deal with more than one at the same time, eg coordinates):

   package Mace is
      type Thing is private;
      procedure Set_Attribute (Into : in out Thing; Value : Integer);
      function Get_Attribute (From : Thing) return Integer;
   private
      type Thing is record
         Attribute : Integer;
      end record;
   end Mace;

   package body Mace is
      procedure Set_Attribute (Into : in out Thing; Value : Integer) is
      begin
         Into.Attribute := Value;
      end Set_Attribute;
      function Get_Attribute (From : Thing) return Integer
      is (From.Attribute);
   end Mace;


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

* Re: Calling a record type's methods (functions or procedure) when record is in an array
  2020-01-17 23:30 Calling a record type's methods (functions or procedure) when record is in an array Mace Ayres
  2020-01-18 12:31 ` Simon Wright
@ 2020-01-18 18:02 ` Mace Ayres
  2020-01-18 20:53   ` Simon Wright
  2020-01-21 20:51   ` Shark8
  2020-01-19 15:06 ` Mace Ayres
  2 siblings, 2 replies; 12+ messages in thread
From: Mace Ayres @ 2020-01-18 18:02 UTC (permalink / raw)


Thank you. I see, we can pass the record (type) thing as a parameter, along with any other parameters (like value) and then interact with the record ‘thing’  in sub programs. 

Since my objects (type of Thing) are only instantiated as elements in my array, thing_array, I can only/ would I address them like this ?

looping.. i
 looping  j
   set_attribute(my_thing_array(i,j).value, 6);
  ...
end loop;
end loop;

In this way I only access (not ACCESS type) my thing via set_attribute procedure and not with...  thing.value := 5, which is the direct access we want to avoid. 

And with type thing being private, its attributes are only accessible via sub programs in package Mace.

In your code below with my mark up “ * ?”,  are the sub programs private in any way since they are below  Type Thing is private, or the privacy is applied to Thing?

That is, what is the full scope of privacy in declaring type thing as private, to type thing only,  or the sub programs too. Or is this a confused question anyway?


? this code does indeed access the value fields directly!

-- I have to add the private part too, to hide the inners of type
a_trunk.

You're looking for an accessor (though accessors aren't always a good
idea; there might be checks needed, attributes may be related so you
need to deal with more than one at the same time, eg coordinates):

 package Mace is
    type Thing is private;
 * ?    procedure Set_Attribute (Into : in out Thing; Value : Integer);
 * ?   function Get_Attribute (From : Thing) return Integer;
 private
    type Thing is record
       Attribute : Integer;
    end record;
 end Mace;

 package body Mace is
    procedure Set_Attribute (Into : in out Thing; Value : Integer) is
    begin
       Into.Attribute := Value;
    end Set_Attribute;
    function Get_Attribute (From : Thing) return Integer
    is (From.Attribute);
 end Mace;


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

* Re: Calling a record type's methods (functions or procedure) when record is in an array
  2020-01-18 18:02 ` Mace Ayres
@ 2020-01-18 20:53   ` Simon Wright
  2020-01-21 20:51   ` Shark8
  1 sibling, 0 replies; 12+ messages in thread
From: Simon Wright @ 2020-01-18 20:53 UTC (permalink / raw)


Mace Ayres <maceayres0@gmail.com> writes:

> Thank you. I see, we can pass the record (type) thing as a parameter,
> along with any other parameters (like value) and then interact with
> the record ‘thing’ in sub programs.

Yes.

> Since my objects (type of Thing) are only instantiated as elements in
> my array, thing_array, I can only/ would I address them like this ?
>
> looping.. i
>  looping  j
>    set_attribute(my_thing_array(i,j).value, 6);
>   ...
> end loop;
> end loop;

> And with type thing being private, its attributes are only accessible
> via sub programs in package Mace.

Yes.

> In your code below with my mark up “ * ?”, are the sub programs
> private in any way since they are below Type Thing is private, or the
> privacy is applied to Thing?
>
> That is, what is the full scope of privacy in declaring type thing as
> private, to type thing only, or the sub programs too. Or is this a
> confused question anyway?

>>  package Mace is
>>     type Thing is private;
>>  * ?    procedure Set_Attribute (Into : in out Thing; Value : Integer);
>>  * ?   function Get_Attribute (From : Thing) return Integer;
>>  private
>>     type Thing is record
>>        Attribute : Integer;
>>     end record;
>>  end Mace;

The package spec has a public part (everything above the 'private' in
the left margin of line 5) and a private part (everything after).

The two subprograms are publicly visible.

You need a tutorial! Try https://learn.adacore.com
and specifically about privacy
https://learn.adacore.com/courses/intro-to-ada/chapters/privacy.html
or look here for lots of learning material
https://www.adaic.org/learn/materials/#tutorials


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

* Re: Calling a record type's methods (functions or procedure) when record is in an array
  2020-01-17 23:30 Calling a record type's methods (functions or procedure) when record is in an array Mace Ayres
  2020-01-18 12:31 ` Simon Wright
  2020-01-18 18:02 ` Mace Ayres
@ 2020-01-19 15:06 ` Mace Ayres
  2 siblings, 0 replies; 12+ messages in thread
From: Mace Ayres @ 2020-01-19 15:06 UTC (permalink / raw)


On Friday, January 17, 2020 at 3:30:54 PM UTC-8, Mace Ayres wrote:
> My package 'trunks.ads' includes 
> ...
> type a_trunk;.
> 
> function set_lock ...  return lock_state;
> 
> function post_val(v:integer) --- return integer
> ...
> type a_trunk is
>   record
>      id : ,,,
>     val
>     ...
>     lock  : lock_state    -- enumeration type defined earlier (open, locked)
>   end record;
> 
> Package body 'trunks.adb  includes ...
> 
> function set_lock (  ..... not relevant
> 
> function post_val i(v:integer)  return integer is ..return v;
> 
> ------
> In package 1 I have a multi dimension array of type a_truck that I get to with
> ..
> loop de loop i,j
> my_trunk_array (i)(j)
> ..
> -------
> 
> To modify the item val in the trunk at array (5)(3) I code..
> 
> ... my_truck_arrary(5)(3).val := trunks.post_val(N)
> 
> rather than my_tunk_arrary(5)(3).val := N
> 
> so I don't directly access the a_trunk record's value fields directly
> 
> -- I have to add the private part too, to hide the inners of type a_trunk.
> 
> It seem a little convoluted, but I see no other way to manipulate my a_truck type records that only 'exist' the array.
> 
> I am just learning Ada. Is this reasonable?

——


Thanks Simon.


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

* Re: Calling a record type's methods (functions or procedure) when record is in an array
  2020-01-18 18:02 ` Mace Ayres
  2020-01-18 20:53   ` Simon Wright
@ 2020-01-21 20:51   ` Shark8
  2020-01-21 23:17     ` Jeffrey R. Carter
  2020-01-23 15:00     ` joakimds
  1 sibling, 2 replies; 12+ messages in thread
From: Shark8 @ 2020-01-21 20:51 UTC (permalink / raw)


On Saturday, January 18, 2020 at 11:02:32 AM UTC-7, Mace Ayres wrote:
> 
> In your code below with my mark up “ * ?”,  are the sub programs private in any way since they are below Type Thing is private, or the privacy is applied to Thing?

Ada has a concept called private types, "TYPE X IS PRIVATE;", where the type's implementation is hidden from the clients of the package. Thus you could have the following:

Package Example is
   Type Point is private;
  
   -- Getters:
   Function  X( Object : in     Point ) return Integer;
   Function  Y( Object : in     Point ) return Integer;
  
   -- Setters:
   Procedure X( Object : in out Point; Value : in     Integer );
   Procedure Y( Object : in out Point; Value : in     Integer );
Private
  
   Type Point is record
     X_Value, Y_Value : -- Integer;
                         Real;
   End record;
End Example;

Package Body Example is
   Function  X( Object : in     Point ) return Integer is
   Begin
    Return Integer(Object.X_Value);
   End X;
  
   Procedure X( Object : in out Point; Value : in     Integer )
   Begin
    Object.X_Value:= Real( Value );
   End X;

   Function  Y( Object : in     Point ) return Integer is
   Begin
    Return Integer(Object.Y_Value);
   End Y;
  
   Procedure Y( Object : in out Point; Value : in     Integer ) is
   Begin
    Object.Y_Value:= Real( Value );
   End Y;

End Example;

And now, you could change the type of the components to Point to Integer, remove the type-casts, and recompile the package Example **without having to recompile dependent packages** because they are dependent only on the visible portion of the package.

> 
> That is, what is the full scope of privacy in declaring type thing as private, to type thing only,  or the sub programs too. Or is this a confused question anyway?

See above.
Private types are Ada's method of hiding implementation-details. For example, you could have a Password type that, internally, is a string but none of the package-clients can see that:

Package Other_Example is
  Min_Length : Constant Natural;
  Function Valid_Characters( Input : String ) return Boolean;
  
  Type Password(<>) is private;
  
  
  Function Create( Input : String ) return Password
   with Pre => Valid_Characters(Input) and Input'Length >= Min_Length;
  Function "="( Left, Right : Password ) return Boolean;
  Function "="( Object : Password; Value : String ) return Boolean;
  
Private
  
  -- A Password must be at least 5 characters,
  -- and may contain only alphanumeric characters.
  Min_Length : Constant Natural:= 5;
  Function Valid_Characters( Input : String ) return Boolean is
  (for all C of Password => C in 'a'..'z'|'A'..'Z'|'0'..'9');
  
  Type Password is new String
    with Dynamic_Predicate => Password'Length >= Min_Length
        and then Valid_Characters( String(Password) );
  
    Function Create( Input : String ) return Password is
    ( Password(Input) );
End Other_Example;


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

* Re: Calling a record type's methods (functions or procedure) when record is in an array
  2020-01-21 20:51   ` Shark8
@ 2020-01-21 23:17     ` Jeffrey R. Carter
  2020-01-23 15:00     ` joakimds
  1 sibling, 0 replies; 12+ messages in thread
From: Jeffrey R. Carter @ 2020-01-21 23:17 UTC (permalink / raw)


On 1/21/20 9:51 PM, Shark8 wrote:
> 
> And now, you could change the type of the components to Point to Integer, remove the type-casts, and recompile the package Example **without having to recompile dependent packages** because they are dependent only on the visible portion of the package.

Most, if not all, compilers will require you to recompile clients of the package 
because they use the full type declaration for allocating space for objects of 
the private type.

-- 
Jeff Carter
"This trial is a travesty. It's a travesty of a mockery of a
sham of a mockery of a travesty of two mockeries of a sham. ...
Do you realize there's not a single homosexual on that jury?"
Bananas
27


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

* Re: Calling a record type's methods (functions or procedure) when record is in an array
  2020-01-21 20:51   ` Shark8
  2020-01-21 23:17     ` Jeffrey R. Carter
@ 2020-01-23 15:00     ` joakimds
  2020-01-23 15:02       ` joakimds
  2020-01-23 20:15       ` Optikos
  1 sibling, 2 replies; 12+ messages in thread
From: joakimds @ 2020-01-23 15:00 UTC (permalink / raw)


> And now, you could change the type of the components to Point to Integer, remove the type-casts, and recompile the package Example **without having to recompile  dependent packages** because they are dependent only on the visible portion of the package.

Using Taft types introduced in Ada95 it is possible to add new components to a record type without recompilation of dependent packages. Here is an Ada 2005 example:

private with System.Storage_Elements;

package Cars is

   type Any_Car (<>) is limited private;
   --  This type is defined with unknown discriminant in order to make
   --  sure instances are properly initialized by allocator function.

   function Allocate_Car return Any_Car;
   --  The allocator function.

   type Car_Passenger_Count is range 0 .. 5;
   
   function Passenger_Count (Car : Any_Car) return Car_Passenger_Count;

   procedure Set_Passenger_Count
     (Car   : in out Any_Car;
      Value : Car_Passenger_Count);

private

   type Taft_Car;

   type Taft_Car_Ptr is access all Taft_Car;

   type Any_Car
     (Offset : System.Storage_Elements.Storage_Offset)
   is limited record
      Allocated_Memory : aliased
        System.Storage_Elements.Storage_Array (1 .. Offset);
      Reference : Taft_Car_Ptr;
   end record;

end Cars;



with System.Address_To_Access_Conversions;

package body Cars is

   type Taft_Car is record
      Passenger_Count : Car_Passenger_Count;
   end record;

   package Conversions is new System.Address_To_Access_Conversions
     (Object => Taft_Car);

   function Allocate_Car return Any_Car is
      Default : constant Any_Car
        := (Offset           => Taft_Car'Max_Size_In_Storage_Elements,
            Allocated_Memory => (others => 0),
            Reference        => null);
   begin
      return Car : Any_Car (Taft_Car'Max_Size_In_Storage_Elements) do
         declare
            First_Index : constant System.Storage_Elements.Storage_Offset
              := Car.Allocated_Memory'First;
         begin
            Car.Reference := Conversions.To_Pointer
              (Car.Allocated_Memory (First_Index)'Address).all'Access;
         end;
      end return;
   end Allocate_Car;

   function Passenger_Count (Car : Any_Car) return Car_Passenger_Count is
   begin
      return Car.Reference.Passenger_Count;
  end Passenger_Count;

   procedure Set_Passenger_Count
     (Car   : in out Any_Car;
      Value : Car_Passenger_Count) is
   begin
      Car.Reference.all.Passenger_Count := Value;
   end Set_Passenger_Count;
   
end Cars;


with Ada.Text_IO;

with Cars;
use  Cars;

procedure Main is
   Car : Cars.Any_Car := Cars.Allocate_Car;
begin
   Set_Passenger_Count (Car, 3);
   Ada.Text_IO.Put_Line (Passenger_Count (Car)'Image);
end Main;

Does somebody have a better implementation of Taft types where heap allocations are not used?

Perhaps this example is something to add to documentation on Ada on the internet like for example:
https://en.wikibooks.org/wiki/Ada_Programming/Tips

Anything wrong or could be improved with the implementation above?

Best regards,
Joakim


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

* Re: Calling a record type's methods (functions or procedure) when record is in an array
  2020-01-23 15:00     ` joakimds
@ 2020-01-23 15:02       ` joakimds
  2020-01-23 16:51         ` Simon Wright
  2020-01-23 20:15       ` Optikos
  1 sibling, 1 reply; 12+ messages in thread
From: joakimds @ 2020-01-23 15:02 UTC (permalink / raw)


Obvious copy paste error:

   function Allocate_Car return Any_Car is
      Default : constant Any_Car
        := (Offset           => Taft_Car'Max_Size_In_Storage_Elements,
            Allocated_Memory => (others => 0),
            Reference        => null);
   begin
      return Car : Any_Car (Taft_Car'Max_Size_In_Storage_Elements) do
         declare
            First_Index : constant System.Storage_Elements.Storage_Offset
              := Car.Allocated_Memory'First;
         begin
            Car.Reference := Conversions.To_Pointer
              (Car.Allocated_Memory (First_Index)'Address).all'Access;
         end;
      end return;
   end Allocate_Car;

should be:

   function Allocate_Car return Any_Car is
   begin
      return Car : Any_Car (Taft_Car'Max_Size_In_Storage_Elements) do
         declare
            First_Index : constant System.Storage_Elements.Storage_Offset
              := Car.Allocated_Memory'First;
         begin
            Car.Reference := Conversions.To_Pointer
              (Car.Allocated_Memory (First_Index)'Address).all'Access;
         end;
      end return;
   end Allocate_Car; 

Other issues?

Best regards,
Joakim

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

* Re: Calling a record type's methods (functions or procedure) when record is in an array
  2020-01-23 15:02       ` joakimds
@ 2020-01-23 16:51         ` Simon Wright
  2020-01-24  9:47           ` joakimds
  0 siblings, 1 reply; 12+ messages in thread
From: Simon Wright @ 2020-01-23 16:51 UTC (permalink / raw)


joakimds@kth.se writes:

> Other issues?

Alignment?

=========

Looks to me like something it would be better not to do, even if you can.

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

* Re: Calling a record type's methods (functions or procedure) when record is in an array
  2020-01-23 15:00     ` joakimds
  2020-01-23 15:02       ` joakimds
@ 2020-01-23 20:15       ` Optikos
  1 sibling, 0 replies; 12+ messages in thread
From: Optikos @ 2020-01-23 20:15 UTC (permalink / raw)


On Thursday, January 23, 2020 at 9:00:18 AM UTC-6, joak...@kth.se wrote:
> > And now, you could change the type of the components to Point to Integer, remove the type-casts,
> > and recompile the package Example **without having to recompile  dependent packages** because
> > they are dependent only on the visible portion of the package.
> 
> Using Taft types introduced in Ada95 it is possible to add new components to a record type without
> recompilation of dependent packages. Here is an Ada 2005 example:
> 
> private with System.Storage_Elements;
> 
> package Cars is
> 
>    type Any_Car (<>) is limited private;
>    --  This type is defined with unknown discriminant in order to make
>    --  sure instances are properly initialized by allocator function.
> 
>    function Allocate_Car return Any_Car;
>    --  The allocator function.
> 
>    type Car_Passenger_Count is range 0 .. 5;
>    
>    function Passenger_Count (Car : Any_Car) return Car_Passenger_Count;
> 
>    procedure Set_Passenger_Count
>      (Car   : in out Any_Car;
>       Value : Car_Passenger_Count);
> 
> private
> 
>    type Taft_Car;
> 
>    type Taft_Car_Ptr is access all Taft_Car;
> 
>    type Any_Car
>      (Offset : System.Storage_Elements.Storage_Offset)
>    is limited record
>       Allocated_Memory : aliased
>         System.Storage_Elements.Storage_Array (1 .. Offset);
>       Reference : Taft_Car_Ptr;
>    end record;
> 
> end Cars;
> 
> 
> 
> with System.Address_To_Access_Conversions;
> 
> package body Cars is
> 
>    type Taft_Car is record
>       Passenger_Count : Car_Passenger_Count;
>    end record;
> 
>    package Conversions is new System.Address_To_Access_Conversions
>      (Object => Taft_Car);
> 
>    function Allocate_Car return Any_Car is
>       Default : constant Any_Car
>         := (Offset           => Taft_Car'Max_Size_In_Storage_Elements,
>             Allocated_Memory => (others => 0),
>             Reference        => null);
>    begin
>       return Car : Any_Car (Taft_Car'Max_Size_In_Storage_Elements) do
>          declare
>             First_Index : constant System.Storage_Elements.Storage_Offset
>               := Car.Allocated_Memory'First;
>          begin
>             Car.Reference := Conversions.To_Pointer
>               (Car.Allocated_Memory (First_Index)'Address).all'Access;
>          end;
>       end return;
>    end Allocate_Car;
> 
>    function Passenger_Count (Car : Any_Car) return Car_Passenger_Count is
>    begin
>       return Car.Reference.Passenger_Count;
>   end Passenger_Count;
> 
>    procedure Set_Passenger_Count
>      (Car   : in out Any_Car;
>       Value : Car_Passenger_Count) is
>    begin
>       Car.Reference.all.Passenger_Count := Value;
>    end Set_Passenger_Count;
>    
> end Cars;
> 
> 
> with Ada.Text_IO;
> 
> with Cars;
> use  Cars;
> 
> procedure Main is
>    Car : Cars.Any_Car := Cars.Allocate_Car;
> begin
>    Set_Passenger_Count (Car, 3);
>    Ada.Text_IO.Put_Line (Passenger_Count (Car)'Image);
> end Main;
> 
> Does somebody have a better implementation of Taft types where heap allocations are not used?
> 
> Perhaps this example is something to add to documentation on Ada on the internet like for example:
> https://en.wikibooks.org/wiki/Ada_Programming/Tips
> 
> Anything wrong or could be improved with the implementation above?
> 
> Best regards,
> Joakim

Background on "Taft types" (a.k.a. Ichbiah's name "Taft-amendment types" or the generic/language-independent name "opaque pointers" or the C++ jargon "pimpl").
https://groups.google.com/forum/#!msg/comp.lang.ada/KelH3y5WzEA/z3pyInm_hqgJ


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

* Re: Calling a record type's methods (functions or procedure) when record is in an array
  2020-01-23 16:51         ` Simon Wright
@ 2020-01-24  9:47           ` joakimds
  0 siblings, 0 replies; 12+ messages in thread
From: joakimds @ 2020-01-24  9:47 UTC (permalink / raw)


Den torsdag 23 januari 2020 kl. 17:51:22 UTC+1 skrev Simon Wright:
> joakimds@kth.se writes:
> 
> > Other issues?
> 
> Alignment?
> 
> =========
> 
> Looks to me like something it would be better not to do, even if you can.

Hi Simon,

Not entirely sure how Alignment can interfere but I can realize that using controlled types in the Taft type defined in the body may yield unexpected results. Right now I am leaning towards better not to do even if one can. However, here is another implementation that may be less error prone:

package Cars is

   type Any_Holder is abstract tagged limited null record;
   
   function Make_Holder return Any_Holder'Class;
   
   type Any_Car (<>) is limited private;
   --  This type is defined with unknown discriminant in order to make
   --  sure instances are properly initialized by allocator function.
   
   function Allocate_Car (Holder : in out Any_Holder'Class) return Any_Car;
   --  The allocator function.

   type Car_Passenger_Count is range 0 .. 5;
   
   function Passenger_Count (Car : Any_Car) return Car_Passenger_Count;

   procedure Set_Passenger_Count
     (Car   : in out Any_Car;
      Value : Car_Passenger_Count);

private

   type Taft_Car;

   type Any_Car
     (Reference : not null access Taft_Car)
   is limited null record;

end Cars;

package body Cars is

   type Taft_Car is record
      Passenger_Count : Car_Passenger_Count;
   end record;

   type Car_Holder is new Any_Holder with record
      Car : aliased Taft_Car;
   end record;
   
   function Make_Holder return Any_Holder'Class is
   begin
      return C : Car_Holder do
         C.Car.Passenger_Count := 0;
      end return;
   end Make_Holder;

   function Allocate_Car (Holder : in out Any_Holder'Class) return Any_Car is
      H : Car_Holder renames Car_Holder (Holder);
   begin
      return Car : Any_Car (H.Car'Access) do
         null;
      end return;
   end Allocate_Car;

   function Passenger_Count (Car : Any_Car) return Car_Passenger_Count is
   begin
      return Car.Reference.Passenger_Count;
   end Passenger_Count;

   procedure Set_Passenger_Count
     (Car   : in out Any_Car;
      Value : Car_Passenger_Count) is
   begin
      Car.Reference.all.Passenger_Count := Value;
   end Set_Passenger_Count;
   
end Cars;

with Ada.Text_IO;

with Cars;
use  Cars;

procedure Main is
   Holder : Cars.Any_Holder'Class := Cars.Make_Holder;
   Car : Cars.Any_Car := Cars.Allocate_Car (Holder);
begin
   Set_Passenger_Count (Car, 3);
   Ada.Text_IO.Put_Line (Passenger_Count (Car)'Image);
end Main;

The issues with the above implementation is:
1. Usage of downward conversion at "H : Car_Holder renames Car_Holder (Holder);". It is a feature of Ada that can lead to inefficient code generation and there is a gnatcheck or AdaControl rule to check/forbid such usage.
2. Usage of anonymous access type "(Reference : not null access Taft_Car)". It isn't obvious from the code as it is written that it is correct although it is accepted by the GNAT compiler due to the complexity of the anonymous access type rules. Perhaps somebody in the Ada community would like to motivate using the anonymous access type rules in the Reference Manual why it is correct? :)

Best regards,
Joakim


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

end of thread, other threads:[~2020-01-24  9:47 UTC | newest]

Thread overview: 12+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2020-01-17 23:30 Calling a record type's methods (functions or procedure) when record is in an array Mace Ayres
2020-01-18 12:31 ` Simon Wright
2020-01-18 18:02 ` Mace Ayres
2020-01-18 20:53   ` Simon Wright
2020-01-21 20:51   ` Shark8
2020-01-21 23:17     ` Jeffrey R. Carter
2020-01-23 15:00     ` joakimds
2020-01-23 15:02       ` joakimds
2020-01-23 16:51         ` Simon Wright
2020-01-24  9:47           ` joakimds
2020-01-23 20:15       ` Optikos
2020-01-19 15:06 ` Mace Ayres

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