comp.lang.ada
 help / color / mirror / Atom feed
Search results ordered by [date|relevance]  view[summary|nested|Atom feed]
thread overview below | download mbox.gz: |
* Getting the index for an element in mutually referencing containers
@ 2017-03-09 13:45  7% Mart van de Wege
  0 siblings, 0 replies; 15+ results
From: Mart van de Wege @ 2017-03-09 13:45 UTC (permalink / raw)



I am missing another thing: I managed to boil down the problem to the
PoC code below. I want to have two objects, each with a container as a
record attribute, referring to each other, and then merely get the index
value of one of the two containers. Yet if I do, I get a Storage_Error
exception.

Code:

with Ada.Containers.Indefinite_Vectors;
with Ada.Containers.Indefinite_Doubly_Linked_Lists;
with Ada.Integer_Text_IO; use Ada.Integer_Text_IO;
procedure Test_Container is
   type Abstract_Person is abstract tagged null record;
   package Offspring is new Ada.Containers.Indefinite_Vectors
     (Index_Type => Positive,
      Element_Type => Abstract_Person'Class);
   package Group is new Ada.Containers.Indefinite_Doubly_Linked_Lists
     (Element_Type => Abstract_Person'Class);
   type Person is new Abstract_Person with record
      Children : Offspring.Vector := Offspring.To_Vector(4);
      Parents : Group.List;
   end record;
   Father : Person;
   Child : Person;
begin
   Child.Parents.Prepend(Father);
   Father.Children.Append(Child);
   Put(Integer(Father.Children.Find_Index(Child)));
end Test_Container;

This compiles OK, but on runtime throws an exception:

raised STORAGE_ERROR : stack overflow or erroneous memory access

Now, cyclic dependencies are tricky, so I am sure I am doing something
wrong, but I can't for the life of me see what.

Mart

-- 
"We will need a longer wall when the revolution comes."
    --- AJS, quoting an uncertain source.

^ permalink raw reply	[relevance 7%]

* Re: Can't access record attribute in derived type
  2017-03-08 21:03  5% ` Shark8
@ 2017-03-08 21:16  0%   ` Mart van de Wege
  0 siblings, 0 replies; 15+ results
From: Mart van de Wege @ 2017-03-08 21:16 UTC (permalink / raw)


Shark8 <onewingedshark@gmail.com> writes:

> On Wednesday, March 8, 2017 at 7:15:22 AM UTC-7, Mart van de Wege wrote:
>> Hi,
>> 
>> I have the following definitions
>> 
>> private
>> type Creature is new Base_Creature with record
>>       Attributes	 : Attribute_Array;
>>       Gender             : Possible_Gender := Unknown;
>>       Current_Hit_Points : Integer;
>>       Parents            : Group_Of_Creatures.List;
>>       --  An instance of Ada.Containers.Indefinite_Doubly_Linked_Lists
>> end record;
>> 
>> In child package #1 (Persons):
>> 
>> private
>>    type Person is new Creature with record
>>    [...]
>> and in child package #2 (Knights):
>>    type Knight is new Person with record
>>    [...]
>> 
>> I try to read the first element of the Parents attribute in knights.adb
>> like this:
>> 
>>    function Father (K : in Knight) return Knight is
>>    begin
>>       return K.Parents.First_Element;
>>    end Father;
>
> One Problem is that K.Parents.First_Element *isn't* of type Knight --
> It's of type Creature -- that is surely one problem.
>
Yeah, that is solved by some explicit conversions. I am not happy with
that, but this is still the first phase of my attempt at implementing
families, and getting my head around the intricacies of OO in Ada.

> Secondly, the construct 
>> type Creature is new Base_Creature with record
>>       Attributes	 : Attribute_Array;
>>       Gender             : Possible_Gender := Unknown;
>>       Current_Hit_Points : Integer;
>>       Parents            : Group_Of_Creatures.List;
>>       --  An instance of Ada.Containers.Indefinite_Doubly_Linked_Lists
>> end record;
> cannot exist, as you cannot instantiate the Container without completing the type which can't be complete without the instantiation of the Container (because of the Parents element).
>
> I would recommend something like this:
>
>     Type Base_Creature is abstract tagged record
>        Attributes         : Attribute_Array;
>        Gender             : Possible_Gender := Unknown;
>        Current_Hit_Points : Integer;
>     end record;
>
> --...
>     Package Creature_Grouping is new Ada.Containers.Indefinite_Doubly_Linked_Lists( Base_Creature'Class );
> --...
That's more or less what I did. Creature is derived from abstract
Base_Creature, and Group_Of_Creatures is defined as new
Ada.Containers.Indefinite_Doubly_Linked_list (Element_Type =>
Base_Creature'Class).

Mart

-- 
"We will need a longer wall when the revolution comes."
    --- AJS, quoting an uncertain source.


^ permalink raw reply	[relevance 0%]

* Re: Can't access record attribute in derived type
  2017-03-08 14:15  5% Can't access record attribute in derived type Mart van de Wege
  2017-03-08 20:08  0% ` Randy Brukardt
@ 2017-03-08 21:03  5% ` Shark8
  2017-03-08 21:16  0%   ` Mart van de Wege
  1 sibling, 1 reply; 15+ results
From: Shark8 @ 2017-03-08 21:03 UTC (permalink / raw)


On Wednesday, March 8, 2017 at 7:15:22 AM UTC-7, Mart van de Wege wrote:
> Hi,
> 
> I have the following definitions
> 
> private
> type Creature is new Base_Creature with record
>       Attributes	 : Attribute_Array;
>       Gender             : Possible_Gender := Unknown;
>       Current_Hit_Points : Integer;
>       Parents            : Group_Of_Creatures.List;
>       --  An instance of Ada.Containers.Indefinite_Doubly_Linked_Lists
> end record;
> 
> In child package #1 (Persons):
> 
> private
>    type Person is new Creature with record
>    [...]
> and in child package #2 (Knights):
>    type Knight is new Person with record
>    [...]
> 
> I try to read the first element of the Parents attribute in knights.adb
> like this:
> 
>    function Father (K : in Knight) return Knight is
>    begin
>       return K.Parents.First_Element;
>    end Father;

One Problem is that K.Parents.First_Element *isn't* of type Knight -- It's of type Creature -- that is surely one problem.

Secondly, the construct 
> type Creature is new Base_Creature with record
>       Attributes	 : Attribute_Array;
>       Gender             : Possible_Gender := Unknown;
>       Current_Hit_Points : Integer;
>       Parents            : Group_Of_Creatures.List;
>       --  An instance of Ada.Containers.Indefinite_Doubly_Linked_Lists
> end record;
cannot exist, as you cannot instantiate the Container without completing the type which can't be complete without the instantiation of the Container (because of the Parents element).

I would recommend something like this:

    Type Base_Creature is abstract tagged record
       Attributes         : Attribute_Array;
       Gender             : Possible_Gender := Unknown;
       Current_Hit_Points : Integer;
    end record;

--...
    Package Creature_Grouping is new Ada.Containers.Indefinite_Doubly_Linked_Lists( Base_Creature'Class );
--...

    Type Creature is new Base_Creature with record
       Parents : Creature_Grouping.List;
    end record;

--...
    Type Person is new Creature with --[...]
    Function Father( Input : Person ) return Creature'Class is
      ( Input.Parents.First_Element );
--...
    Type Knight is new Person with --[...]

^ permalink raw reply	[relevance 5%]

* Re: Can't access record attribute in derived type
  2017-03-08 14:15  5% Can't access record attribute in derived type Mart van de Wege
@ 2017-03-08 20:08  0% ` Randy Brukardt
  2017-03-08 21:03  5% ` Shark8
  1 sibling, 0 replies; 15+ results
From: Randy Brukardt @ 2017-03-08 20:08 UTC (permalink / raw)



"Mart van de Wege" <mvdwege@gmail.com> wrote in message 
news:86mvcv4zyu.fsf@gaheris.avalon.lan...
> Hi,
>
> I have the following definitions
>
> private
> type Creature is new Base_Creature with record
>      Attributes : Attribute_Array;
>      Gender             : Possible_Gender := Unknown;
>      Current_Hit_Points : Integer;
>      Parents            : Group_Of_Creatures.List;
>      --  An instance of Ada.Containers.Indefinite_Doubly_Linked_Lists
> end record;
>
> In child package #1 (Persons):
>
> private
>   type Person is new Creature with record
>   [...]
> and in child package #2 (Knights):
>   type Knight is new Person with record
>   [...]
>
> I try to read the first element of the Parents attribute in knights.adb
> like this:
>
>   function Father (K : in Knight) return Knight is
>   begin
>      return K.Parents.First_Element;
>   end Father;
>
> And the compiler complains:
>
> "no selector "Parents" for type "Knight" defined"
>
> What am I missing here? The declarations are private, but shouldn't a
> tagged type inherit the entire record of its parent type? That means
> that it should have a Parents selector, shouldn't it?

I suspect we'll need to see a more complete example to definitively say what 
the problem is.

But if I had to guess, I'd suggest that you've run afoul of the "sibling 
inheritance problem". The rule for visibility for child components is that 
*all* of components of the *all* of the ancestors have to be visible at the 
point of declaration of the child type. If even one of the ancestors is not 
visible (as happens when deriving from a type defined in a sibling child 
package), then the components aren't visible, either.

Note that in such a case, if you have visiblity on some but not all of the 
ancestors, you can type convert the object to make them visible. In your 
example above:

     return Creature(K).Parents.First_Element;

will work if you have some intermediate ancestor without visible components. 
So, if the above works, you have a sibling inheritance problem, and your 
choices are either to use conversions like the above, or move the types so 
that all of the ancestors are visible.

                                     Randy.



^ permalink raw reply	[relevance 0%]

* Can't access record attribute in derived type
@ 2017-03-08 14:15  5% Mart van de Wege
  2017-03-08 20:08  0% ` Randy Brukardt
  2017-03-08 21:03  5% ` Shark8
  0 siblings, 2 replies; 15+ results
From: Mart van de Wege @ 2017-03-08 14:15 UTC (permalink / raw)


Hi,

I have the following definitions

private
type Creature is new Base_Creature with record
      Attributes	 : Attribute_Array;
      Gender             : Possible_Gender := Unknown;
      Current_Hit_Points : Integer;
      Parents            : Group_Of_Creatures.List;
      --  An instance of Ada.Containers.Indefinite_Doubly_Linked_Lists
end record;

In child package #1 (Persons):

private
   type Person is new Creature with record
   [...]
and in child package #2 (Knights):
   type Knight is new Person with record
   [...]

I try to read the first element of the Parents attribute in knights.adb
like this:

   function Father (K : in Knight) return Knight is
   begin
      return K.Parents.First_Element;
   end Father;

And the compiler complains:

 "no selector "Parents" for type "Knight" defined"

What am I missing here? The declarations are private, but shouldn't a
tagged type inherit the entire record of its parent type? That means
that it should have a Parents selector, shouldn't it?

Mart

-- 
"We will need a longer wall when the revolution comes."
    --- AJS, quoting an uncertain source.


^ permalink raw reply	[relevance 5%]

* Mutating elements of constant list using a container element iterator
@ 2015-08-04 23:56  6% martinbbjerregaard
  0 siblings, 0 replies; 15+ results
From: martinbbjerregaard @ 2015-08-04 23:56 UTC (permalink / raw)


Mutating elements of a constant container in a "for ... of ... loop" is possible with the "standard" container types but not the indefinite or bounded containers:

with Ada.Containers.Doubly_Linked_Lists;
with Ada.Containers.Indefinite_Doubly_Linked_Lists;

procedure Strange_Behavior is
   
   type Test is tagged
      record
         Value : Integer;
      end record;
   
   package Test_Lists is new Ada.Containers.Doubly_Linked_Lists (Element_Type => Test);
   package Test_Indefinite_Lists is new Ada.Containers.Indefinite_Doubly_Linked_Lists (Element_Type => Test);
   
   function Make_List return Test_Lists.List is
   begin
      return Result : Test_Lists.List := Test_Lists.Empty_List do
         for I in 0 .. 100 loop
            Result.Append (Test'(Value => I));
         end loop;
      end return;
   end Make_List;
   
   function Make_Indefinite_List return Test_Indefinite_Lists.List is
   begin
      return Result : Test_Indefinite_Lists.List := Test_Indefinite_Lists.Empty_List do
         for I in 0 .. 100 loop
            Result.Append (Test'(Value => I));
         end loop;
      end return;
   end Make_Indefinite_List;
   
   V1 : constant Test_Lists.List := Make_List;
   V2 : constant Test_Indefinite_Lists.List := Make_Indefinite_List;
   
begin
   
   for Item of V1 loop
      Item.Value := 0; -- no error
   end loop;
   
   for Item of V2 loop
      Item.Value := 0; -- error: "left hand side of assignment must be a variable"
   end loop;
   
end Strange_Behavior;

http://www.ada-auth.org/standards/12rat/html/Rat12-8-3.html says:
"If we write
for E of The_List loop
   ...   -- do something to Element E
end loop;
then we can change the element E unless The_List has been declared as constant."

Is this a bug?


^ permalink raw reply	[relevance 6%]

* Re: S-expression I/O in Ada
  @ 2010-08-24 11:41  3%       ` Natasha Kerensikova
  0 siblings, 0 replies; 15+ results
From: Natasha Kerensikova @ 2010-08-24 11:41 UTC (permalink / raw)


Hello,

Here is my second try at a in-memory S-expression package. I used
Doubly_Linked_Lists, but I did my best to make it as easy as possible to
switch to Vectors.

I managed to remove all explicit access, except for callbacks.

I face the difficulty of trying to make as few list assignments as
possible, because they trigger deep-copy. The problem is that the
package is supposed to be fed directly from external data, which might
be unsafe. So I don't want deep copyings all over the place, because it
might become very expensive on specially-crafted deep input.

Inspired from Ada containers interface (i.e. Cursors), I think the
interface here is usable for read a S-expression object.

However I couldn't imagine a way to design S-expression construction
interface without triggering a deep copy. Ada containers use
Update_Element, which requires passing a read-write container. So in
order to Append a node to a List (let's call it L), I need to pass L's
parent in read-write mode. However in order to get a read-write access
to L's parent, I need to pass L's grandparent to something, which
requires L's grand-grandparent, and so on until the unknown root list.
Obviously this doesn't work.

Using the Append procedure implemented here, I can insert a List as a
node at the end of an existing List, but that makes a deep copy of the
inserted List. So using this interface, if we imagine more and more
complex objects containing less complex object, it means making a simple
list, deep-copying into a large list, itself deep-copied into a larger
list, itself deep-copied into an even larger list, and so-on. While it's
bounded by the application rather than as user input, which is less bad,
it seems sounds horribly inefficient.

Does anybody have an idea about how to solve this issue?


Another point I discovered while writing this implementation, is that I
end up writing a lot of wrappers over the container's functions. Would
it be possible to somehow define List and Cursors directly as instances
of the container respective types, and to expose directly container's
functions? All this while maintaining the type hiding, I don't want to
expose the container, and just want to specify "I expose this and that
functions" and tell in the body "oh by the way, this and that functions
are just public names of this and that container functions". This way
the code would be lighter but still as flexible (whenever I'm not
satisfied with container functions, or whenever I want to change the
container, I just have to (re)write the publicly exposed functions
without changing the specification).

Or is it just completely insane?


Also, I find this implementation much more complex than I expected
for a conceptually simple object. I'm afraid I got caught up into some
design hell and came up with something much more complex than needed.
However I can't see how I can make it simpler without giving up to the
deep-copy issue. Is it because I'm a noob or because it really has to be
that complex?


I believe I would be much more at ease with a custom access-based
singly-linked list implementation, but I'm afraid this is due to my
excessive use of C pointers. I still can't estimate how bad or inelegant
or ugly are explicit access. I guess even in Ada they have some niche
use, and avoiding expensive copy can be one them, right?


Another thing I noticed with this relatively large package is Ada
verbosity. Now I see the difference between using words versus {}. The
problem I see with words for everything is that identifiers don't come
out as well (even with syntax highlighting, differently-colored words
have less contrast than words and punctuation). I hope it's only because
I'm still misusing whitespace.

I'm used to 8-column tab for indentation in C, is it completely
unrealistic in Ada? I followed the recommendation of 3-space
indentation, and that's very flat. Again, do I need only time to get
used to it, or are there other lighter whitespace styles that I haven't
encountered yet?


Last point, I had trouble finding names. I read the Ada 95 Quality and
Style Guide, and I find it difficult to follow. For example, I was
tempted to call "Atom" the public array representation, the internal
node type, and the function taking a Cursor and returning the public
array representation. I was tempted to call "Node_Type" the public
enumeration type, the function taking a Cursor and returning the type of
the pointed node, and (not in this implementation but in some other
attempts) the internal object discriminant name.

Does it become easier with practice? Would you mind reviewing my name
choices to progress faster?


As usual, all comments on my code are welcome, especially those that can
make me progress.
Thanks in advance for your help,
Natasha





with Ada.Containers;
use  Ada.Containers;

private with Ada.Containers.Indefinite_Doubly_Linked_Lists;


package S_Expressions is

   -----------
   -- Types --
   -----------

   type Octet is range 0 .. 255;
   type Atom_Data is array (Integer range <>) of Octet;
      -- Atom_Data is public to allow Object <--> Atom conversion anywhere

   type List is tagged private;
      -- a S-experssion is actually a List object
      -- theoretically any List tail should be a valid S-expression,
      --    but it seems to difficult and not useful enough
      -- each element is either an Atom or a List

   type Cursor is private;
      -- designates an element in a List

   type Node_Kind is (Node_Atom, Node_List);



   ---------------
   -- Constants --
   ---------------

   Empty_List : constant List;
   No_Element : constant Cursor;


   ------------------------------------
   -- String vs Atom_Data converters --
   ------------------------------------

   procedure String_To_Atom(S : in String; A : out Atom_Data);
   procedure Atom_To_String(A : in Atom_Data; S : out String);
   function To_Atom(S : in String) return Atom_Data;
   function To_String(A : in Atom_Data) return String;


   ---------------------
   -- List inspection --
   ---------------------

   procedure Counts(sexp : in List; Atom_Count, List_Count : out Count_Type);
   function Atom_Count(sexp : in List) return Count_Type;
   function List_Count(sexp : in List) return Count_Type;
   function Node_Count(sexp : in List) return Count_Type;


   ---------------
   -- Iterators --
   ---------------

   procedure Iterate(sexp         : in List;
                     Process_Atom : access procedure(Atom : in Atom_Data);
                     Process_List : access procedure(Sublist : in List));
   procedure Iterate_Over_Atoms(sexp    : in List;
                                Process : not null access procedure
                                             (Atom : in Atom_Data));
   procedure Iterate_Over_Lists(sexp    : in List;
                                Process : not null access procedure
                                             (Sublist : in List));


   -----------------------
   -- Cursor management --
   -----------------------

   function First(sexp : in List) return Cursor;
   function Last(sexp : in List) return Cursor;

   procedure Next(Position : in out Cursor);
   procedure Previous(Position : in out Cursor);
   function Next(Position : in Cursor) return Cursor;
   function Previous(Position : in Cursor) return Cursor;

   function Is_Atom(Element : in Cursor) return Boolean;
   function Is_List(Element : in Cursor) return Boolean;
   function Kind_Of(Element : in Cursor) return Node_Kind;


   --------------------
   -- Atom accessors --
   --------------------

   procedure Query_Atom(Element : in Cursor;
                        Process : not null access procedure
                                       (Atom : in Atom_Data));
   function Atom_Size(Element : in Cursor) return Natural;
   function Atom_Contents(Element : in Cursor) return Atom_Data;
   function Atom_To_String(Element : in Cursor) return String;


   --------------------
   -- List accessors --
   --------------------

   procedure Query_List(Element : in Cursor;
                        Process : not null access procedure
                                       (Sub_Sexp : in List));
   function Sublist_First(Element : in Cursor) return Cursor;
   function Sublist_Last(Element : in Cursor) return Cursor;


   -----------------------
   -- Node constructors --
   -----------------------


   procedure Append(Target : in out List; Data : in Atom_Data);
      -- Append a new atom to the target list
   procedure Append(Target : in out List; Data : in String);
      -- Append a new atom built from a String to the target list
   procedure Append(Target : in out List; Data : in List);
      -- Append a copy of the given list to the target list



private

   ----------------------
   -- Type definitions --
   ----------------------

   type Node is tagged null record;

   package Lists is new Ada.Containers.Indefinite_Doubly_Linked_Lists
                        (Element_Type => Node'Class);

   type Atom (Size : Natural) is new Node with
      record
         Internal : Atom_Data (1 .. Size);
      end record;

   type List is new Node with
      record
         Internal : Lists.List;
      end record;

   type Cursor is
      record
         Internal : Lists.Cursor;
      end record;


   ---------------
   -- Constants --
   ---------------

   Empty_List : constant List := List'(Internal => Lists.Empty_List);
   No_Element : constant Cursor := Cursor'(Internal => Lists.No_Element);

end S_Expressions;




with Ada.Tags;

package body S_Expressions is

   -----------------------------------
   -- Tag related private functions --
   -----------------------------------


   function Is_Atom(N : in Node'Class) return Boolean is
   begin
      return Ada.Tags."="(N'Tag, Atom'Tag);
   end;

   function Is_List(N : in Node'Class) return Boolean is
   begin
      return Ada.Tags."="(N'Tag, List'Tag);
   end;

   function Kind_Of(N : in Node'Class) return Node_Kind is
      ret : Node_Kind;
   begin
      if Is_Atom(N) then
         ret := Node_Atom;
      elsif Is_List(N) then
         ret := Node_List;
      else
         raise Program_Error;
      end if;
      return ret;
   end Kind_Of;

   pragma Inline(Is_Atom, Is_List, Kind_Of);



   ------------------------------------
   -- String vs Atom_Data converters --
   ------------------------------------

   procedure String_To_Atom(S : in String; A : out Atom_Data) is
   begin
      for i in S'Range loop
         A(i - S'First + A'First) := Character'Pos(S(i)) - 1;
      end loop;
   end String_To_Atom;



   procedure Atom_To_String(A : in Atom_Data; S : out String) is
   begin
      for i in A'Range loop
         S(i - A'First + S'First) := Character'Val(A(i) + 1);
      end loop;
   end Atom_To_String;



   function To_Atom(S : in String) return Atom_Data is
      ret : Atom_Data(1 .. S'Length);
   begin
      String_To_Atom(S, ret);
      return ret;
   end To_Atom;



   function To_String(A : in Atom_Data) return String is
      ret : String(A'Range);
   begin
      Atom_To_String(A, ret);
      return ret;
   end To_String;


   ---------------------
   -- List inspection --
   ---------------------


   procedure Counts(sexp : in List; Atom_Count, List_Count : out Count_Type) is

      procedure Process(Element : in Node'Class) is
      begin
         case Kind_Of(Element) is
            when Node_Atom =>
               Atom_Count := Atom_Count + 1;
            when Node_List =>
               List_Count := List_Count + 1;
         end case;
      end;

      procedure Process(Position : in Lists.Cursor) is
      begin
         Lists.Query_Element(Position, Process'Access);
      end Process;

   begin
      Atom_Count := 0;
      List_Count := 0;
      Lists.Iterate(sexp.Internal, Process'Access);
   end Counts;



   function Atom_Count(sexp : in List) return Count_Type is
      ret, discard : Count_Type;
   begin
      Counts(sexp, ret, discard);
      return ret;
   end;



   function List_Count(sexp : in List) return Count_Type is
      ret, discard : Count_Type;
   begin
      Counts(sexp, discard, ret);
      return ret;
   end;



   function Node_Count(sexp : in List) return Count_Type is
   begin
      return Lists.Length(sexp.Internal);
   end;



   ---------------
   -- Iterators --
   ---------------

   procedure Iterate(sexp         : in List;
                     Process_Atom : access procedure(Atom : in Atom_Data);
                     Process_List : access procedure(Sublist : in List)) is
      procedure Process(N : in Node'Class) is
      begin
         case Kind_Of(N) is
            when Node_Atom => Process_Atom(Atom(N).Internal);
            when Node_List => Process_List(List(N));
         end case;
      end Process;

      procedure Read_Element(C : in Lists.Cursor) is
      begin
         Lists.Query_Element(C, Process'Access);
      end;

   begin
      if Process_Atom = null then
         if Process_List /= null then
            Iterate_Over_Lists(sexp, Process_List);
         end if;
      else
         if Process_List = null then
            Iterate_Over_Atoms(sexp, Process_Atom);
         else
            Lists.Iterate(sexp.Internal, Read_Element'Access);
         end if;
      end if;
   end Iterate;



   procedure Iterate_Over_Atoms(sexp    : in List;
                                Process : not null access procedure
                                             (Atom : in Atom_Data)) is
      procedure Internal_Process(N : Node'Class) is
      begin
         if Is_Atom(N) then
            Process(Atom(N).Internal);
         end if;
      end Internal_Process;

      procedure Read_Element(C : in Lists.Cursor) is
      begin
         Lists.Query_Element(C, Internal_Process'Access);
      end;

   begin
      Lists.Iterate(sexp.Internal, Read_Element'Access);
   end Iterate_Over_Atoms;



   procedure Iterate_Over_Lists(sexp    : in List;
                                Process : not null access procedure
                                             (Sublist : in List)) is
      procedure Internal_Process(N : Node'Class) is
      begin
         if Is_List(N) then
            Process(List(N));
         end if;
      end Internal_Process;

      procedure Read_Element(C : in Lists.Cursor) is
      begin
         Lists.Query_Element(C, Internal_Process'Access);
      end;

   begin
      Lists.Iterate(sexp.Internal, Read_Element'Access);
   end Iterate_Over_Lists;



   -----------------------
   -- Cursor management --
   -----------------------


   function First(sexp : in List) return Cursor is
      ret : Cursor := (Internal => Lists.First(sexp.Internal));
   begin
      return ret;
   end First;



   function Last(sexp : in List) return Cursor is
      ret : Cursor := (Internal => Lists.Last(sexp.Internal));
   begin
      return ret;
   end Last;



   procedure Next(Position : in out Cursor) is
   begin
      Lists.Next(Position.Internal);
   end Next;



   procedure Previous(Position : in out Cursor) is
   begin
      Lists.Previous(Position.Internal);
   end Previous;



   function Next(Position : in Cursor) return Cursor is
      ret : Cursor := (Internal => Lists.Next(Position.Internal));
   begin
      return ret;
   end Next;



   function Previous(Position : in Cursor) return Cursor is
      ret : Cursor := (Internal => Lists.Previous(Position.Internal));
   begin
      return ret;
   end Previous;



   function Is_Atom(Element : in Cursor) return Boolean is
   begiN
      return Element /= No_Element
         and then Lists.Has_Element(Element.Internal)
         and then Kind_Of(Element) = Node_Atom;
   end Is_Atom;



   function Is_List(Element : in Cursor) return Boolean is
   begiN
      return Element /= No_Element
         and then Lists.Has_Element(Element.Internal)
         and then Kind_Of(Element) = Node_List;
   end Is_List;



   function Kind_Of(Element : in Cursor) return Node_Kind is
      ret : Node_Kind;
      procedure Process(Element : in Node'Class) is
      begin
         ret := Kind_Of(Element);
      end;
   begin
      Lists.Query_Element(Element.Internal, Process'Access);
      return ret;
   end Kind_Of;



   --------------------
   -- Atom accessors --
   --------------------


   procedure Query_Atom(Element : in Cursor;
                        Process : not null access procedure
                                       (Atom : in Atom_Data)) is
      procedure Internal_Process(Element : in Node'Class) is
      begin
         Process(Atom(Element).Internal);
      end Internal_Process;
   begin
      Lists.Query_Element(Element.Internal, Internal_Process'Access);
   end Query_Atom;



   function Atom_Size(Element : in Cursor) return Natural is
      ret : Natural;
      procedure Record_Size(Element : in Node'Class) is
      begin
         ret := Atom(Element).Size;
      end Record_Size;
   begin
      Lists.Query_Element(Element.Internal, Record_Size'Access);
      return ret;
   end Atom_Size;



   function Atom_Contents(Element : in Cursor) return Atom_Data is
      ret : Atom_Data(1 .. Atom_Size(Element));
      procedure Copy_Atom_Data(Element : in Node'Class) is
      begin
         ret := Atom(Element).Internal;
      end;
   begin
      Lists.Query_Element(Element.Internal, Copy_Atom_Data'Access);
      return ret;
   end Atom_Contents;



   function Atom_To_String(Element : in Cursor) return String is
      ret : String(1 .. Atom_Size(Element));
      procedure To_String(Element : in Node'Class) is
         input : Atom_Data renames Atom(Element).Internal;
      begin
         Atom_To_String(Atom(Element).Internal, ret);
      end;
   begin
      Lists.Query_Element(Element.Internal, To_String'Access);
      return ret;
   end Atom_To_String;



   --------------------
   -- List accessors --
   --------------------


   procedure Query_List(Element : in Cursor;
                        Process : not null access procedure
                                       (Sub_Sexp : in List)) is
      procedure Internal_Process(Element : in Node'Class) is
      begin
         Process(List(Element));
      end Internal_Process;
   begin
      Lists.Query_Element(Element.Internal, Internal_Process'Access);
   end Query_List;



   function Sublist_First(Element : in Cursor) return Cursor is
      ret : Cursor;
      procedure Make_First(Element : in Node'Class) is
      begin
         ret.Internal := Lists.First(List(Element).Internal);
      end Make_First;
   begin
      Lists.Query_Element(Element.Internal, Make_First'Access);
      return ret;
   end Sublist_First;



   function Sublist_Last(Element : in Cursor) return Cursor is
      ret : Cursor;
      procedure Make_Last(Element : in Node'Class) is
      begin
         ret.Internal := Lists.Last(List(Element).Internal);
      end Make_Last;
   begin
      Lists.Query_Element(Element.Internal, Make_Last'Access);
      return ret;
   end Sublist_Last;


   -----------------------
   -- Node constructors --
   -----------------------


   procedure Append(Target : in out List; Data : in Atom_Data) is
      Neo_Node : Atom(Data'Length);
   begin
      Neo_Node.Internal(1 .. Data'Length) := Data(Data'Range);
      Lists.Append(Target.Internal, Neo_Node);
   end Append;



   procedure Append(Target : in out List; Data : in String) is
      Neo_Node : Atom(Data'Length);
   begin
      String_To_Atom(Data, Neo_Node.Internal);
      Lists.Append(Target.Internal, Neo_Node);
   end Append;



   procedure Append(Target : in out List; Data : in List) is
   begin
      Lists.Append(Target.Internal, Data);
   end Append;



end S_Expressions;



^ permalink raw reply	[relevance 3%]

* Re: Types, packages & objects : the good old naming conventions question (without religious ware)
  2009-10-31 11:58  7%       ` Stephen Leake
  2009-11-02 20:36  0%         ` Georg Bauhaus
@ 2009-11-02 21:47  0%         ` Randy Brukardt
  1 sibling, 0 replies; 15+ results
From: Randy Brukardt @ 2009-11-02 21:47 UTC (permalink / raw)


"Stephen Leake" <stephen_leake@stephe-leake.org> wrote in message 
news:uskcz6ahs.fsf@stephe-leake.org...
...
> Here are the similar definitions from
> Ada.Containers.Indefinite_Doubly_Linked_Lists. I hope you won't start
> arguing that is a bad abstraction.
>
> package Ada.Containers.Indefinite_Doubly_Linked_Lists is
>
>   type List is tagged private;
>
>   generic
>      with function "<" (Left, Right : Element_Type) return Boolean is <>;
>   package Generic_Sorting is
>
>      function Is_Sorted (Container : List) return Boolean;
>   end Generic_Sorting;
> end Ada.Containers.Indefinite_Doubly_Linked_Lists;
>
> Note that it uses _Type for Element!

If anyone cares, that's because we used a form of Stephen's rules for naming 
these. In this case, we determined that the best name ("Element") should be 
reserved for the operation, as the operation will likely be used many times, 
while the formal type name is hardly ever written in client code (just as a 
name in the instance) -- note this ties into one of the previous threads 
here. We considered using longer names for the operation like "Get_Element", 
"Read_Element", etc., but those just made the name longer without adding 
enough additional information. After all, an important rule is to make names 
long enough to capture all of the critical information, but no longer 
(because there is a point where names get too long for readability).

                     Randy.





^ permalink raw reply	[relevance 0%]

* Re: Types, packages & objects : the good old naming conventions question (without religious ware)
  2009-10-31 11:58  7%       ` Stephen Leake
@ 2009-11-02 20:36  0%         ` Georg Bauhaus
  2009-11-02 21:47  0%         ` Randy Brukardt
  1 sibling, 0 replies; 15+ results
From: Georg Bauhaus @ 2009-11-02 20:36 UTC (permalink / raw)


Stephen Leake schrieb:

> Nonsense; it is _precisely_ what I want; a list of abstract objects.
> 
> You can't avoid the naming problem by changing the context!

But there should be better ways to resolve the naming problem
when changing context.  Better than being unspecific, that is:
it sure is possible, if redundant, to give a hint to the
context.

> Here are the similar definitions from
> Ada.Containers.Indefinite_Doubly_Linked_Lists. I hope you won't start
> arguing that is a bad abstraction.

No, though it is perhaps notworthy that IIRC the container
type's name used to be "Container" in every package in some
earlier editions.  (I couldn't resist saying some more on
names and abstract programming in another reply.)


> Note that it uses _Type for Element!

I think Element_Type was not chosen in order to take sides with
the _Type convention.


> How is that better than this:
> 
> package Ada.Containers.Indefinite_Doubly_Linked_Lists is
> 
>    type List_Type is tagged private;
> 
>    generic
>       with function "<" (Left, Right : Element_Type) return Boolean is <>;
>    package Generic_Sorting is
> 
>       function Is_Sorted (List : List_Type) return Boolean;
>    end Generic_Sorting;

There are fewer occurrences of "List" that need disambiguation.
But I'll happily leave it to that empirical study of the effects
of naming conventions whether other solutions work better or
worse.

>> (Rules here: Bits _of_ something, sensor _of_ something,
>> these are examples following Tom Moran's comment, if I'm
>> not mistaken. Names Sensor and Bits are really quite abstract.
>> I would force them to be used for abstract types' names, at best.)
> 
> Yes, if you have a specific context and a specific meaning, then you
> should use a specific name. The corollary is that if you have a
> generic context, you should use a generic name.

But is the generic context really unspecifiable, i.e.,
do we have to become vague in our naming?
We could state, using names, or adorned names, or ...,
that something is useful in many specific cases.
This fact is a distinguishing feature.



> [List]
> 
> Who said this was a linked list?

Any programmer with a Lisp background will assume List is :-)

If what matters is the set of operations needed,
then is it not possible to specify a frame of reference
for this particular meaning of "List"?


> [SAL] "list" tends to imply some access order, meaning there is at
> least First, Next, Is_Done. Containers don't have those functions.

This is where conventions can cause problems.

package Ada.Containers.Hashed_Sets is
  ...
  function First (Container : Set) return Cursor;

SAL and Ada.Containers differ in their approaches to the same problem,
both using the same names connected to incompatible set of operations...



>> generic
>>     type Less_Equal is new Ordering with private;
>> procedure Sort (Container : in out Linked_List);
>>
>> Is anything lost here?  
> 
> Yes! You have lost the fact that this is a generic procedure that
> doesn't care about the internal structure of the list.

OK. But then, personally, I would have though that (or the
abstract linking you have mentioned) would distinguish a List.

> You have also
> lost the ability to specify the Order at run-time.

Why?  Can't I instantiate with any Ordering type from
any block that happens to be visited at run time?


> And "less_equal" implies a mathematical sort. All I really need for a
> sort that produces a linear order is "goes_before".

"Goes_Before" a better name, then.  Though it corresponds to "Less"
only, not "Less_Equal", doesn't it?  (I'm desparately looking
for how the [= relation is pronounced.  Not_After?)

>> I think Dylan made an attempt, at least if one is satified with "car"
>> being in a different namespace than "<car>".
> 
> Clearly it's a different name; it's a different lexeme. That's
> the same as the _Type convention. 

I think this is significant:  Many of us care about lexemes
much less than digital computers in that we rather correct
oddities like spelling errors or <framings> in letter patterns.


>> I'd still not pick essentially the same name for object Car
>> and type Car though. Even if Ada had one namespace for types
>> and one for other entities.  An object is never the same
>> as a type, therefore it should be possible to distinguish
>> the difference using words.
> 
> Yes! Car is distinguished from Car_Type, but List is not distinguished
> from Container. Thank you for agreeing with me :).

OK, to me, Car_Type is only minimally different from Car,
and not sufficiently.  In particular, the difference carries
no meaning in either the objects domain, or in the comain
of the value sets of types.
(I guess we both would not write procedure Speed_Subprogram (...))


> Actually, I disagree with this statement; overloading types and
> objects is fine, since the language does make the distinction clear
> from context. In Dylan, I would use "car" and "<car>".
> 
> It sounds like you don't like overloading in the first place. How
> about this: 
> 
>     adding integers is never the same as adding float; it should be
>     possible to distinguish the difference using words

OCaml does, though with a bit of black dirt only.

> So you don't like "+" (Left, Right : in Integer) and "+" (Left, Right
> : in Float)?
> 
> If you do like operator overloading, how is that different from
> object/type overloading?

I don't like conventional operators in Ada programs,
and more so in C programs:
They create a huge set of problems when people think
they know what they are doing when writing "+".



^ permalink raw reply	[relevance 0%]

* Re: Types, packages & objects : the good old naming conventions question (without religious ware)
  @ 2009-10-31 11:58  7%       ` Stephen Leake
  2009-11-02 20:36  0%         ` Georg Bauhaus
  2009-11-02 21:47  0%         ` Randy Brukardt
  0 siblings, 2 replies; 15+ results
From: Stephen Leake @ 2009-10-31 11:58 UTC (permalink / raw)


Georg Bauhaus <rm.dash-bauhaus@futureapps.de> writes:

> Stephen Leake schrieb:
>> Georg Bauhaus <rm.dash-bauhaus@futureapps.de> writes:
>> 
>>> Hibou57 (Yannick Duch�ne) schrieb:
>>>
>>>> There is on the other hand, this other convention, which came from
>>>> Pascal I suppose : the one which ends types name with the suffix _Type
>>> If you can't find a name for an object, ask more questions
>>> about it, its use, its relations, the programmer, its purpose,
>>> his purpose, etc:
>>> What is the role of the object?  Does the role lead to a name?
>> 
>> Why should I have to waste time on this?
>
> Because the time "wasted" on thinking about the roles (properties,
> relations, ...) of named entities in your programs, and
> then not being silent about your results, instead naming the
> entities suitably according to your results, and explicitly
> saying what you mean, is
>
> (a) spent anyway, though to different extents, on this very
>     issue

Yes, but that applies to both the object name and the type name;
making them _different_ requires _extra_ effort.

> P1 (in the kitchen): "P2? Mind giving me that?"
> P2 (in the living room): "What?"
> P1: "That thing over there."
> P2: "Where?"
> P1 (approaches):  "There." (P2 moves) "No, there."
> "No, not that, that!"

This is _not_ a good analogy; "that" is not a subprogram parameter in
the kitchen!

>>     procedure Sort (List : in out List; Order : in Order_Type);
>
> "List" is a darn bad abstraction name here!  

Nonsense; it is _precisely_ what I want; a list of abstract objects.

You can't avoid the naming problem by changing the context!

Here are the similar definitions from
Ada.Containers.Indefinite_Doubly_Linked_Lists. I hope you won't start
arguing that is a bad abstraction.

package Ada.Containers.Indefinite_Doubly_Linked_Lists is

   type List is tagged private;

   generic
      with function "<" (Left, Right : Element_Type) return Boolean is <>;
   package Generic_Sorting is

      function Is_Sorted (Container : List) return Boolean;
   end Generic_Sorting;
end Ada.Containers.Indefinite_Doubly_Linked_Lists;

Note that it uses _Type for Element!

How is that better than this:

package Ada.Containers.Indefinite_Doubly_Linked_Lists is

   type List_Type is tagged private;

   generic
      with function "<" (Left, Right : Element_Type) return Boolean is <>;
   package Generic_Sorting is

      function Is_Sorted (List : List_Type) return Boolean;
   end Generic_Sorting;

end Ada.Containers.Indefinite_Doubly_Linked_Lists;

> (For illustration we could similarly praise a ubuquituous type name
> such as "Bits" when what is meant is
> "Temperature_Sensor.Connector_Bits", say.)

But nothing specific is "meant" here; it is a generic, in the truest
English meaning of that word.

> (Rules here: Bits _of_ something, sensor _of_ something,
> these are examples following Tom Moran's comment, if I'm
> not mistaken. Names Sensor and Bits are really quite abstract.
> I would force them to be used for abstract types' names, at best.)

Yes, if you have a specific context and a specific meaning, then you
should use a specific name. The corollary is that if you have a
generic context, you should use a generic name.

> List in your original example without the Order parameter was
> almost certainly a Partial_Order even without an Order parameter
> in sight (since in the modified example you have given in this
> posting there is an Order parameter).  Next, the List is a partial
> order of element of some type.  Only in a reusable subprogram
> their type, if irrelevant, adds but noise (as per Bob Duff's rule).
> Since there is now an explicit Order parameter, I will assume
> that the List is really just a set of items without an order,
> and the name "List" only alludes to the mode of accessing
> the elements (sequentially, linked in some unknown way).

Ok.

> If I understand "Sort" meant as a generically useful procedure,
> then, as Dmitry has said, the first argument can be named "Container",
> since it contains the elements of the list (the type of Container).

Obviously; that's the approach Ada.Containers takes. It can also be
named "list", since that means exactly the same thing. Or the type can
be named "container", for the same reason.

There is the large risk that one person will decide on :

    procedure Sort (Container : in out List);

and another will choose:

    procedure Sort (List : in out Container);    

Now somebody has to decide, and one has to go back and make lots of
trivial (and therefore error-prone) edits.

I suppose one person could choose List_Type and the other
Container_Type, but at least that's a smaller fix to unify them.

> Without some hint to an order, a type name "List" says enough about
> the structure of the actual parameter (Container).
>
> "Order" is somewhat unspecific.  

Yes, deliberately.

> The "List" context helps when guessing that Order refers to a
> mathematical ordering relation. Its not a call to order, say, in a
> program controlling the president's electronic bell in some
> parliament.

Yes, obviously; this is a programming language context, not "the real
world".

> Inside the procedure, you might want to emphasize the links of
> the elements to be sorted.

Who said this was a linked list? Ada.Containers.Doubly_Linked_Lists
is, my original example doesn't care. I guess you could be refering to
abstract links.

See http://www.stephe-leake.org/ada/sal.html
sal-gen-alg-find_linear-sorted.ads for an abstract sort procedure. It
uses Container and Container_Type; "list" does have the connotation of
"linked list", "container" is slightly more abstract. But I often use
the name "list" for an implementation that happens to be an unbounded
array; "list" tends to imply some access order, meaning there is at
least First, Next, Is_Done. Containers don't have those functions.

> One way to achieve this is to rename the parameter "Container"
> to "Linked_Elements" (I'd think it is somewhat pompous, though.
> The implementer will know how to deal with the name Container.
> The reader of Sort's body will know what Container is, too.
> Because the type name, such as "Linked_List" gives the necessary
> information.)

That would be wrong; you are adding/imposing a structure that is not
necessarily there.

> generic
>     type Less_Equal is new Ordering with private;
> procedure Sort (Container : in out Linked_List);
>
> Is anything lost here?  

Yes! You have lost the fact that this is a generic procedure that
doesn't care about the internal structure of the list. You have also
lost the ability to specify the Order at run-time.

And "less_equal" implies a mathematical sort. All I really need for a
sort that produces a linear order is "goes_before". We tend to map all
things into numbers, so "less_equal" makes sense. But it's really
better to say "A goes before B", instead of "A is less than B".

"Ordering" could also imply a partial order, as for military rank; all
generals first, then all lieutenants, seargents, etc. Less_Equal can
mean that, but "Military_Rank" would be clearer.

>>> Naming conventions always make me think of features
>>> that a language does not offer.  I don't think this is
>>> the case with types and objects in Ada.
>> 
>> It _is_ the case for Ada! The feature "separate name spaces for types
>> and objects" is not offered by Ada. I'm not aware of a language that
>> does offer this feature, but it certainly is within the realm of
>> possibility.
>
> I think Dylan made an attempt, at least if one is satified with "car"
> being in a different namespace than "<car>".

Clearly it's a different name; it's a different lexeme. That's
the same as the _Type convention. 

> I'd still not pick essentially the same name for object Car
> and type Car though. Even if Ada had one namespace for types
> and one for other entities.  An object is never the same
> as a type, therefore it should be possible to distinguish
> the difference using words.

Yes! Car is distinguished from Car_Type, but List is not distinguished
from Container. Thank you for agreeing with me :).

Actually, I disagree with this statement; overloading types and
objects is fine, since the language does make the distinction clear
from context. In Dylan, I would use "car" and "<car>".

It sounds like you don't like overloading in the first place. How
about this: 

    adding integers is never the same as adding float; it should be
    possible to distinguish the difference using words

So you don't like "+" (Left, Right : in Integer) and "+" (Left, Right
: in Float)?

If you do like operator overloading, how is that different from
object/type overloading?

-- 
-- Stephe



^ permalink raw reply	[relevance 7%]

* Re: Ada.Containers.Indefinite_Doubly_Linked_Lists
  2007-02-05 17:47 14% Ada.Containers.Indefinite_Doubly_Linked_Lists Carroll, Andrew
  2007-02-05 18:33  6% ` Ada.Containers.Indefinite_Doubly_Linked_Lists Jeffrey R. Carter
@ 2007-02-05 20:39  6% ` Niklas Holsti
  1 sibling, 0 replies; 15+ results
From: Niklas Holsti @ 2007-02-05 20:39 UTC (permalink / raw)


Carroll, Andrew wrote:
> [ ... ]
> Package Attribute_List is new new
> Ada.Containers.Indefinite_Doubly_Linked_Lists (Attribute);
> 
> Type Table is record
> 	Name: String(50);
> 	Attributes:  Attribute_List;
                      ^^^^^^^^^^^^^^
Should be            Attribute_List.List;
because Attribute_List is a package that manages lists of Attributes, 
not a data type. The data type is Attribute_List.List.

> End record

> Package Table_List is new Ada.Containers.Indefinite_Doubly_Linked_Lists
> (Table);

I find it clearer to use names in plural form for packages that manage 
many objects of a given type. In this case I would use the name 
Attribute_Lists (not ..._List) for the package that manages lists of 
Attribute objects (each such list is an object of type 
Attribute_Lists.List). I would use the name Table_Lists for the package 
that manages lists of Table objects (each such list is an object of type 
Table_Lists.List).

The language-defined Ada packages use the same convention, for example 
Ada.Containers.Doubly_Linked_Lists (not ..._List). Of course you can use 
any names you like.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .



^ permalink raw reply	[relevance 6%]

* Re: Ada.Containers.Indefinite_Doubly_Linked_Lists
  2007-02-05 17:47 14% Ada.Containers.Indefinite_Doubly_Linked_Lists Carroll, Andrew
@ 2007-02-05 18:33  6% ` Jeffrey R. Carter
  2007-02-05 20:39  6% ` Ada.Containers.Indefinite_Doubly_Linked_Lists Niklas Holsti
  1 sibling, 0 replies; 15+ results
From: Jeffrey R. Carter @ 2007-02-05 18:33 UTC (permalink / raw)


Carroll, Andrew wrote:
> 
> Type Attribute is record
> 	Name: String(50);
> 	Type: String(25);

Type, of course, is a reserved word. String is an unconstrained array 
type, and needs to be constrained by a range:

Name : String (1 .. 50);

Note that Name will always be 50 characters. If you want Names of 
varying lengths, Unbounded_String is probably the easiest way to go.

> I'm kind of lost though as to where these package declarations should
> go.  Should they be like:
> 
> Package Table_List_Thingy is
> 
> 	Type Attribute is record
> 		Name: String(50);
> 		Type: String(25);
> 		...
> 	End record;
> 
> 	Package Attribute_List is new new
> Ada.Containers.Indefinite_Doubly_Linked_Lists (Attribute);
> 
> OR
> 
> Procedure RunMe(...) is 
> 
> 	Type Attribute is record
> 		Name: String(50);
> 		Type: String(25);
> 		...
> 	End record;
> 
> 	Package Attribute_List is new new
> Ada.Containers.Indefinite_Doubly_Linked_Lists (Attribute);

Yes. Either will work. Which you should use depends on the problem and 
your design. (Here we encounter one of Ada's most valuable features: you 
have to think about design before you start coding.)

It doesn't look as if you need the indefinite version for either of your 
lists.

-- 
Jeff Carter
"Spam! Spam! Spam! Spam! Spam! Spam! Spam! Spam!"
Monty Python's Flying Circus
53



^ permalink raw reply	[relevance 6%]

* Ada.Containers.Indefinite_Doubly_Linked_Lists
@ 2007-02-05 17:47 14% Carroll, Andrew
  2007-02-05 18:33  6% ` Ada.Containers.Indefinite_Doubly_Linked_Lists Jeffrey R. Carter
  2007-02-05 20:39  6% ` Ada.Containers.Indefinite_Doubly_Linked_Lists Niklas Holsti
  0 siblings, 2 replies; 15+ results
From: Carroll, Andrew @ 2007-02-05 17:47 UTC (permalink / raw)
  To: comp.lang.ada

I think then this is basically what I need to do (out of context and
there may be mistakes).

Type Attribute is record
	Name: String(50);
	Type: String(25);
	...
End record;

Package Attribute_List is new new
Ada.Containers.Indefinite_Doubly_Linked_Lists (Attribute);

Type Table is record
	Name: String(50);
	Attributes:  Attribute_List;
End record

Package Table_List is new Ada.Containers.Indefinite_Doubly_Linked_Lists
(Table);



I'm kind of lost though as to where these package declarations should
go.  Should they be like:

Package Table_List_Thingy is

	Type Attribute is record
		Name: String(50);
		Type: String(25);
		...
	End record;

	Package Attribute_List is new new
Ada.Containers.Indefinite_Doubly_Linked_Lists (Attribute);

	Type Table is record
		Name: String(50);
		Attributes:  Attribute_List;
	End record

	Package Table_List is new
Ada.Containers.Indefinite_Doubly_Linked_Lists (Table);

End Table_List_Thingy;


OR

Procedure RunMe(...) is 

	Type Attribute is record
		Name: String(50);
		Type: String(25);
		...
	End record;

	Package Attribute_List is new new
Ada.Containers.Indefinite_Doubly_Linked_Lists (Attribute);

	Type Table is record
		Name: String(50);
		Attributes:  Attribute_List;
	End record

	Package Table_List is new
Ada.Containers.Indefinite_Doubly_Linked_Lists (Table);

Begin
	...

End RunMe;

What are your suggestions?

Andrew



^ permalink raw reply	[relevance 14%]

* Re: Ada.Containers.Doubly_Linked_Lists
  @ 2007-02-05 15:43  5%     ` Matthew Heaney
  0 siblings, 0 replies; 15+ results
From: Matthew Heaney @ 2007-02-05 15:43 UTC (permalink / raw)


On Feb 4, 5:08 pm, Ludovic Brenta <ludo...@ludovic-brenta.org> wrote:
> If all you want is an unbounded string, just say
>
> package Lists_Of_Unbouned_Strings is
>    new Ada.Containers.Doubly_Linked_Lists
>      (Element_Type => Ada.Strings.Unbounded.Unbounded_Strings);
>
> L : Lists_Of_Unbouned_Strings.List;

A cleaner way to do this (that avoids having to use type
Unbounded_String) is:

package String_Lists is
  new Ada.Containers.Indefinite_Doubly_Linked_Lists (String);

procedure Op (L : String_Lists.List) is
begin
  L.Append ("Hello, World!");
end;




^ permalink raw reply	[relevance 5%]

* Re: Access types to records containing strings
  @ 2005-02-15 16:18  5%       ` Matthew Heaney
  0 siblings, 0 replies; 15+ results
From: Matthew Heaney @ 2005-02-15 16:18 UTC (permalink / raw)



Dmitry A. Kazakov wrote:
> On 15 Feb 2005 04:17:13 -0800, Xavier Serrand wrote:
>
> It is what unbounded strings already do. Additionally you will need
to make
> List_Object controlled (to control destruction), which might be
> undesirable.

In Ada 2005, you'll be able to put the strings on the indefinite list
standard container:

package String_Lists is
   new Ada.Containers.Indefinite_Doubly_Linked_Lists (String);

use String_Lists;

procedure Op (L : in out List) is
begin
   L.Append ("Hello, World");
   Replace_Element (Last (L), "Goodbye, World");
end;

No pointers required...

-Matt




^ permalink raw reply	[relevance 5%]

Results 1-15 of 15 | reverse | options above
-- pct% links below jump to the message on this page, permalinks otherwise --
2005-01-29  8:58     Access types to records containing strings Stefan Merwitz
2005-01-29 10:03     ` Dmitry A. Kazakov
2005-02-15 12:17       ` Xavier Serrand
2005-02-15 13:20         ` Dmitry A. Kazakov
2005-02-15 16:18  5%       ` Matthew Heaney
     [not found]     <mailman.69.1170624131.18371.comp.lang.ada@ada-france.org>
2007-02-04 21:35     ` Ada.Containers.Doubly_Linked_Lists Niklas Holsti
2007-02-04 22:08       ` Ada.Containers.Doubly_Linked_Lists Ludovic Brenta
2007-02-05 15:43  5%     ` Ada.Containers.Doubly_Linked_Lists Matthew Heaney
2007-02-05 17:47 14% Ada.Containers.Indefinite_Doubly_Linked_Lists Carroll, Andrew
2007-02-05 18:33  6% ` Ada.Containers.Indefinite_Doubly_Linked_Lists Jeffrey R. Carter
2007-02-05 20:39  6% ` Ada.Containers.Indefinite_Doubly_Linked_Lists Niklas Holsti
2009-10-29 17:11     Types, packages & objects : the good old naming conventions question (without religious ware) Hibou57 (Yannick Duchêne)
2009-10-29 18:11     ` Georg Bauhaus
2009-10-30 10:52       ` Stephen Leake
2009-10-30 13:40         ` Georg Bauhaus
2009-10-31 11:58  7%       ` Stephen Leake
2009-11-02 20:36  0%         ` Georg Bauhaus
2009-11-02 21:47  0%         ` Randy Brukardt
2010-08-01 12:17     S-expression I/O in Ada Natacha Kerensikova
2010-08-17 17:01     ` Natasha Kerensikova
2010-08-17 19:00       ` Jeffrey Carter
2010-08-18 10:49         ` Natasha Kerensikova
2010-08-24 11:41  3%       ` Natasha Kerensikova
2015-08-04 23:56  6% Mutating elements of constant list using a container element iterator martinbbjerregaard
2017-03-08 14:15  5% Can't access record attribute in derived type Mart van de Wege
2017-03-08 20:08  0% ` Randy Brukardt
2017-03-08 21:03  5% ` Shark8
2017-03-08 21:16  0%   ` Mart van de Wege
2017-03-09 13:45  7% Getting the index for an element in mutually referencing containers Mart van de Wege

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