comp.lang.ada
 help / color / mirror / Atom feed
* OO Style with Ada Containers
@ 2007-11-14 23:28 braver
  2007-11-14 23:50 ` Adam Beneschan
                   ` (2 more replies)
  0 siblings, 3 replies; 66+ messages in thread
From: braver @ 2007-11-14 23:28 UTC (permalink / raw)


I've implemented a small system with Ada Containers and am wondering
about how do folks manage to keep their mental faculties together with
it.  Instead of OO's uniquitous Object.method(params), we end up with
something like:

package Some_Things is new Ada.Containers.Things(...)

package ST renames Some_Things;

Something: ST.Type;

while ST.Method(Someting,...) loop
  -- AT is Another_Things instantiation
  ...if AT.Method(Fun(Something), Another_Things.Method(...)) then ...
end if; ...
end loop;

I've found that if I use several components in the same scope, I
introduce renames -- sometimes I get warnings of names hidden due to
clashes, often I enclose heavy usage of a certain container in a

declare
  use Some_Things;
begin
...
end;

-- but this is all very not-warm-and-fuzzy... How do you make the
usage of Ada Containers less verbose?

Cheers,
Alexy




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

* Re: OO Style with Ada Containers
  2007-11-14 23:28 OO Style with Ada Containers braver
@ 2007-11-14 23:50 ` Adam Beneschan
  2007-11-14 23:59   ` braver
  2007-11-19  1:04   ` Matthew Heaney
  2007-11-15  8:43 ` Dmitry A. Kazakov
  2007-11-19  1:03 ` Matthew Heaney
  2 siblings, 2 replies; 66+ messages in thread
From: Adam Beneschan @ 2007-11-14 23:50 UTC (permalink / raw)


On Nov 14, 3:28 pm, braver <delivera...@gmail.com> wrote:
> I've implemented a small system with Ada Containers and am wondering
> about how do folks manage to keep their mental faculties together with
> it.  Instead of OO's uniquitous Object.method(params), we end up with
> something like:
>
> package Some_Things is new Ada.Containers.Things(...)
>
> package ST renames Some_Things;
>
> Something: ST.Type;
>
> while ST.Method(Someting,...) loop
>   -- AT is Another_Things instantiation
>   ...if AT.Method(Fun(Something), Another_Things.Method(...)) then ...
> end if; ...
> end loop;

Ada 2005 does have Object.Method notation (as long as Object's type is
tagged, and I think all the interesting ones in Ada.Containers.***
are).  Did you try it?  Is there something specific that you expected
to work that didn't?  If so, we can certain help you try to track down
the problem.

                          -- Adam





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

* Re: OO Style with Ada Containers
  2007-11-14 23:50 ` Adam Beneschan
@ 2007-11-14 23:59   ` braver
  2007-11-15  0:24     ` braver
  2007-11-19  1:04   ` Matthew Heaney
  1 sibling, 1 reply; 66+ messages in thread
From: braver @ 2007-11-14 23:59 UTC (permalink / raw)


On Nov 15, 2:50 am, Adam Beneschan <a...@irvine.com> wrote:

> Ada 2005 does have Object.Method notation (as long as Object's type is
> tagged, and I think all the interesting ones in Ada.Containers.***
> are).  Did you try it?

Have to say, jumped right in with the Wiki Ada book examples which are
Method(Object, params).  The Rosetta Stone examples also are
procedural-style.  Can you pls show how you use Ordered_Map object-
style?  The sample problem I use is to count all words (space-
separated tokens) in a text file, creating a hash of the form word =>
count.  Also wonder what the current state of string tokenization is
-- tried unconstrained arrays for resulting list of tokens from each
line and couldn't do it as they need to be known size and appending to
them doesn't work.  Didn't want to reallocate with access type on each
token and ended up with Ada.Containers.Vectors for splitting a
String...

Cheers,
Alexy




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

* Re: OO Style with Ada Containers
  2007-11-14 23:59   ` braver
@ 2007-11-15  0:24     ` braver
  2007-11-15  9:36       ` Ludovic Brenta
  2007-11-19  2:24       ` Matthew Heaney
  0 siblings, 2 replies; 66+ messages in thread
From: braver @ 2007-11-15  0:24 UTC (permalink / raw)


OK, here's how I ended up switching most of my sample application to
object-prefix notation.  It gets a Vector of tokens and inserts them
into an Ordered_Map to count word occurrences:

	loop
		Get_Line(Line, Line_Last);
		exit when End_Of_File;
		declare
			use Ngrams.Token_Vectors;
			Tokens : Ngrams.Token_Vector := Ngrams.Split_Vector (Line,
Line_Last);

			Token_Cursor : Cursor := Tokens.First;
			s : SU.Unbounded_String;
			Count : Natural;
		begin
			while Has_Element(Token_Cursor) loop
				s := Element(Token_Cursor);
				-- NB is there a Natural'Inc?
				Total_Word_Count := Total_Word_Count + 1;

				declare
					use Word_Counts;
				begin
					Ngram_Cursor := Ngram_Counts.Find(s);

					-- would need to import "=" for private type WC.Cursor:
					-- if Ngram_Cursor = WC.No_Element
					if not Has_Element(Ngram_Cursor) then
						Ngram_Counts.Insert(s, 1);
						New_Word_Count := New_Word_Count + 1;
					else -- a valid position in Ngram_Pos
						Count := Element(Ngram_Cursor);
						Ngram_Counts.Replace_Element(Ngram_Cursor, Count+1);
						-- or -- but it also replaces the key:
						-- WC.Replace(Ngram_Counts, s, Count+1);
					end if;
				end;

				Next(Token_Cursor);
			end loop;
		end;
	end loop;

	declare
		use Word_Counts;
	begin
		Ngram_Cursor := Ngram_Counts.First;
		while Has_Element(Ngram_Cursor) loop
			Put_Line(SU.To_String(Key(Ngram_Cursor)) &
				Positive'Image(Element(Ngram_Cursor)));
			Next(Ngram_Cursor);
		end loop;
	end;

As you can see, I've managed to do prefix notation everywhere except
cursors.  How do they coexist with prefix notation -- or are they
replaced by something cooler already, too?  :)

I'd appreciate any improvements to the above, which I deduced from ARM
and Rosetta Stone examples in an hour and then prefix'ised thanks to
Adam's hint!  (Well I've followed Ada since 1987 so the spirit is easy
to follow...)

Cheers,
Alexy




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

* Re: OO Style with Ada Containers
  2007-11-14 23:28 OO Style with Ada Containers braver
  2007-11-14 23:50 ` Adam Beneschan
@ 2007-11-15  8:43 ` Dmitry A. Kazakov
  2007-11-15 14:04   ` Maciej Sobczak
  2007-11-19  2:50   ` Matthew Heaney
  2007-11-19  1:03 ` Matthew Heaney
  2 siblings, 2 replies; 66+ messages in thread
From: Dmitry A. Kazakov @ 2007-11-15  8:43 UTC (permalink / raw)


On Wed, 14 Nov 2007 15:28:26 -0800, braver wrote:

> I've implemented a small system with Ada Containers and am wondering
> about how do folks manage to keep their mental faculties together with
> it.

OO is traditionally based on dynamic polymorphism. Ada containers follow
STL design based on templates, i.e. static polymorphism. That isn't much
OO.

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



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

* Re: OO Style with Ada Containers
  2007-11-15  0:24     ` braver
@ 2007-11-15  9:36       ` Ludovic Brenta
  2007-11-15 10:36         ` braver
  2007-11-19  2:36         ` Matthew Heaney
  2007-11-19  2:24       ` Matthew Heaney
  1 sibling, 2 replies; 66+ messages in thread
From: Ludovic Brenta @ 2007-11-15  9:36 UTC (permalink / raw)


braver <deliverable@gmail.com> writes:
> my sample application [...] gets a Vector of tokens and inserts them
> into an Ordered_Map to count word occurrences:

I don't think you need to store all the tokens.  All you need is a
Hashed_Set (which stores objects without duplication).  I would do
something like

   type Word_Counter is
      Word : Ada.Strings.Unbounded.Unbounded_String;
      Count : Natural;
   end Word_Counter;

   function Equivalent (L, R: Word_Counter) is
      use type Ada.Strings.Unbounded.Unbounded_String;
   begin
      return L.Word = R.Word; -- ignore Count in the comparison
   end Equivalent;

   function Hash (Element : Word_Counter) is
   begin
      return Ada.Strings.Unbounded.Hash (Element.Word);
   end Hash;

   package Word_Counter_Hashed_Sets is
     new Ada.Containers.Hadhed_Sets
       (Element_Type => Word_Counter,
        Hash => Hash,
        Equivalent_Elements => Equivalent);

   Counters : Word_Counter_Hashed_Sets.Set;
   Current_Word : Ada.Strings.Unbounded.Unbounded_String;
   Position : Word_Counter_Hashed_Sets.Cursor;
   use type Word_Counter_Hashed_Sets.Cursor;
begin
   ...
   Current_Word := Get_Next_Word;
   Position := Counters.Find (Current_Word);
   if Position = Word_Counter_Hashed_Sets.No_Element then
      Counters.Insert (New_Item => (Word => Current_Word, Count => 1));
   else
      declare
         E : constant Word_Counter := Counters.Element (Position);
      begin
         Counters.Replace_Element
            (Position => Position,
             New_Item => (Word => E.Word, -- [1]
                          Counter => E.Counter + 1));
      end;
   end if;
   ...
end;

(does [1] duplicate E.Word each time we increment the counter?  If so,
consider using
Ada.Containers.Hashed_Sets.Generic_Keys.Update_Element_Preserving_Keys).

> -- would need to import "=" for private type WC.Cursor:
> -- if Ngram_Cursor = WC.No_Element

declare
   use type WC.Cursor;
begin
   if Ngram_Cursor = WC.No_Element then

> I'd appreciate any improvements to the above, which I deduced from ARM

HTH

-- 
Ludovic Brenta.




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

* Re: OO Style with Ada Containers
  2007-11-15  9:36       ` Ludovic Brenta
@ 2007-11-15 10:36         ` braver
  2007-11-15 11:35           ` Ludovic Brenta
  2007-11-19  2:38           ` Matthew Heaney
  2007-11-19  2:36         ` Matthew Heaney
  1 sibling, 2 replies; 66+ messages in thread
From: braver @ 2007-11-15 10:36 UTC (permalink / raw)


Ludovic -- cool!  What about the issue with the cursors operations'
full names -- does one really have to enact `use' clauses to
abbreviate them?

For an object of a tagged type, like Ngram_Counts, I only need to
declare it with the long name of its package type, then employ prefix
notation on the object itself.  Since cursors don't resond to prefix,
I'd have to refer to things like Next(Cursor) for them either with
full names like WC.Next or do `use'.  Can we iterate through all
elements in a collection with solely prefix notation?

Cheers,
Alexy



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

* Re: OO Style with Ada Containers
  2007-11-15 10:36         ` braver
@ 2007-11-15 11:35           ` Ludovic Brenta
  2007-11-15 13:50             ` braver
                               ` (2 more replies)
  2007-11-19  2:38           ` Matthew Heaney
  1 sibling, 3 replies; 66+ messages in thread
From: Ludovic Brenta @ 2007-11-15 11:35 UTC (permalink / raw)


braver writes:
> Ludovic -- cool!  What about the issue with the cursors operations'
> full names -- does one really have to enact `use' clauses to
> abbreviate them?

Cursor types are not tagged, therefore prefixed notation does not work
for them.  It has to be "Position := [Package_Name.]Next (Position)".
But you don't need to do that at all.

Also, you seem to imply that abbreviating cursor operations is a
design goal of yours.  I fail to understand why.  My design goals
would rather be legibility and maintainability and I very seldom use
"use" clauses.

> Can we iterate through all elements in a collection with solely
> prefix notation?

Yes, using Ada.Containers.Hashed_Sets.Iterate.  You pass an access to
a procedure to Iterate and Iterate calls your procedure once for every
element in the container, passing the cursor value.

However in the present case, I advise against iterating over any
container.  My small example uses only Find, Insert, and
Replace_Element for each word in the input file; there is no iteration
over a container.

-- 
Ludovic Brenta.



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

* Re: OO Style with Ada Containers
  2007-11-15 11:35           ` Ludovic Brenta
@ 2007-11-15 13:50             ` braver
  2007-11-19  2:45               ` Matthew Heaney
  2007-11-15 18:22             ` braver
  2007-11-19  2:39             ` Matthew Heaney
  2 siblings, 1 reply; 66+ messages in thread
From: braver @ 2007-11-15 13:50 UTC (permalink / raw)


On Nov 15, 2:35 pm, Ludovic Brenta <ludo...@ludovic-brenta.org>
wrote:
> However in the present case, I advise against iterating over any
> container.  My small example uses only Find, Insert, and
> Replace_Element for each word in the input file; there is no iteration
> over a container.

True -- iteration is needed when we print out the counts.

Back to your original example, why are Ordered_Maps less preferable
than Hashed_Sets?  My code maintains for each distinct word its
overall count, and uses Replace_Element for updating the count -- my
impression is each word is stored just once with that use of
Ordered_Maps, no?  Also, I don't need to give it a hash function.
What are the advantages of Hashed_Sets?

Cheers,
Alexy



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

* Re: OO Style with Ada Containers
  2007-11-15  8:43 ` Dmitry A. Kazakov
@ 2007-11-15 14:04   ` Maciej Sobczak
  2007-11-19  2:53     ` Matthew Heaney
  2007-11-19  2:50   ` Matthew Heaney
  1 sibling, 1 reply; 66+ messages in thread
From: Maciej Sobczak @ 2007-11-15 14:04 UTC (permalink / raw)


On 15 Lis, 09:43, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:

> Ada containers follow
> STL design

Not much.
I would even say that Ada.Containers is somewhere between the two
without being able to really benefit from advantages of any approach.

In paricular, I miss the ability to work with iterators *alone*.

--
Maciej Sobczak * www.msobczak.com * www.inspirel.com



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

* Re: OO Style with Ada Containers
  2007-11-15 11:35           ` Ludovic Brenta
  2007-11-15 13:50             ` braver
@ 2007-11-15 18:22             ` braver
  2007-11-15 20:18               ` Ludovic Brenta
  2007-11-19  2:47               ` Matthew Heaney
  2007-11-19  2:39             ` Matthew Heaney
  2 siblings, 2 replies; 66+ messages in thread
From: braver @ 2007-11-15 18:22 UTC (permalink / raw)


On Nov 15, 2:35 pm, Ludovic Brenta <ludo...@ludovic-brenta.org> wrote:
> Position := Counters.Find (Current_Word);

It turned out this should be

	-- Count can be anything below due to our definition of Equivalent:
	Position := Counters.Find ((Word => Current_Word, Count => 0));

-- which adds to the cumbersomeness of Hashed_Sets vs. Ordered_Maps.
So what are the advantages?

Cheers,
Alexy



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

* Re: OO Style with Ada Containers
  2007-11-15 18:22             ` braver
@ 2007-11-15 20:18               ` Ludovic Brenta
  2007-11-19  2:48                 ` Matthew Heaney
  2007-11-19  2:47               ` Matthew Heaney
  1 sibling, 1 reply; 66+ messages in thread
From: Ludovic Brenta @ 2007-11-15 20:18 UTC (permalink / raw)


braver writes:
> On Nov 15, 2:35 pm, Ludovic Brenta <ludo...@ludovic-brenta.org> wrote:
>> Position := Counters.Find (Current_Word);
>
> It turned out this should be
>
> 	-- Count can be anything below due to our definition of Equivalent:
> 	Position := Counters.Find ((Word => Current_Word, Count => 0));
>
> -- which adds to the cumbersomeness of Hashed_Sets vs. Ordered_Maps.
> So what are the advantages?

I think Find is much more efficient in a Hashed_Set than in an
Ordered_Map because comparing hash values is more efficient than
comparing Unbounded_Strings.  And in the algorithm, we call Find for
each word in the input.

This applies to Insert, too, and we call Insert for every new word in
the input.

How about trying both solutions and benchmarking them?

-- 
Ludovic Brenta.



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

* Re: OO Style with Ada Containers
  2007-11-14 23:28 OO Style with Ada Containers braver
  2007-11-14 23:50 ` Adam Beneschan
  2007-11-15  8:43 ` Dmitry A. Kazakov
@ 2007-11-19  1:03 ` Matthew Heaney
  2 siblings, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19  1:03 UTC (permalink / raw)


braver <deliverable@gmail.com> writes:

> -- but this is all very not-warm-and-fuzzy... How do you make the
> usage of Ada Containers less verbose?

As was pointed out, the container types are tagged, which means you can use
distinguished-receiver syntax.

Cursor types are not tagged, mostly because an operation cannot be primitive
for more than a single tagged type; the container type is already tagged, so
that means the cursor type cannot also be tagged (since they appear together as
parameters in several operations).



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

* Re: OO Style with Ada Containers
  2007-11-14 23:50 ` Adam Beneschan
  2007-11-14 23:59   ` braver
@ 2007-11-19  1:04   ` Matthew Heaney
  1 sibling, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19  1:04 UTC (permalink / raw)


Adam Beneschan <adam@irvine.com> writes:

> Ada 2005 does have Object.Method notation (as long as Object's type is
> tagged, and I think all the interesting ones in Ada.Containers.***
> are).

Right, all the container types are tagged.



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

* Re: OO Style with Ada Containers
  2007-11-15  0:24     ` braver
  2007-11-15  9:36       ` Ludovic Brenta
@ 2007-11-19  2:24       ` Matthew Heaney
  2007-11-23 10:28         ` braver
                           ` (2 more replies)
  1 sibling, 3 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19  2:24 UTC (permalink / raw)


braver <deliverable@gmail.com> writes:

> As you can see, I've managed to do prefix notation everywhere except
> cursors.  How do they coexist with prefix notation -- or are they
> replaced by something cooler already, too?  :)

No, cursors aren't tagged because an operation can only be primitive for a
single tagged type, and the container type is already tagged.


> I'd appreciate any improvements to the above, which I deduced from ARM
> and Rosetta Stone examples in an hour and then prefix'ised thanks to
> Adam's hint!  (Well I've followed Ada since 1987 so the spirit is easy
> to follow...)

The problem with your code is here:

   Ngram_Cursor := Ngram_Counts.Find(s);

   if not Has_Element(Ngram_Cursor) then
       Ngram_Counts.Insert(s, 1);
       New_Word_Count := New_Word_Count + 1;
   else -- a valid position in Ngram_Pos
       Count := Element(Ngram_Cursor);
       Ngram_Counts.Replace_Element(Ngram_Cursor, Count+1);
  end if;


The issue is that Find duplicates the search that must already be performed by
Insert. You don't want to be doing this if the map has many elements.

The solution is to use the conditional form of Insert, which does an atomic
search-and-insert and reports back the result of the search.  If the key is
already in the map, the cursor returned designates the existing key/element
pair (which is not modified); if the key is not in the map, the key/element
pair is inserted and the cursor passed back designates the newly-inserted pair.

What you do here is insert a count of 0 for the word, and then increment the
count. If the word is already in the map, the existing count is increment.  If
the word is not already in the map, the count is 0, so it gets incremented to
the value 1 (which is the desired value).

I have included an example program below.  Also included is a simple scanner
that returns a lexeme for each whitespace-delimited word on a line of text.

Feel free to write if you have any comments or questions.

Regards,
Matt


--STX
with Ada.Command_Line;  use Ada.Command_Line;
with Ada.Text_IO;  use Ada.Text_IO;
with Ada.Integer_Text_IO;  use Ada.Integer_Text_IO;
with Scanners;     use Scanners;
with Ada.Containers.Indefinite_Hashed_Maps;  use Ada.Containers;
with Ada.Strings.Hash_Case_Insensitive;
with Ada.Strings.Equal_Case_Insensitive;  use Ada.Strings;

procedure Count_Words is
   Line      : String (1 .. 256);
   Line_Last : Natural;

   package Map_Types is new Indefinite_Hashed_Maps
     (String,
      Natural,
      Hash_Case_Insensitive,
      Equal_Case_Insensitive);
   
   M : Map_Types.Map;
   use Map_Types;

   F : File_Type;

begin
   Open (F, In_File, Argument (1));

   while not End_Of_File (F) loop
      Get_Line(F, Line, Line_Last);

      declare
         procedure Increment_Count 
           (Word  : String; 
            Count : in out Natural)
         is
         begin
            Count := Count + 1;
         end;

         S : Scanner := Scan (Line (Line'First .. Line_Last));
         
         C : Map_Types.Cursor;
         B : Boolean;

      begin
         while S.Has_Word loop
            M.Insert (S.Word, 0, C, B);
            M.Update_Element (C, Increment_Count'Access);
         end loop;
      end;
   end loop;

   declare
      procedure Process (C : Map_Types.Cursor) is
         Word  : constant String := Key (C);
         Count : constant Natural := Element (C);

      begin
         Put (Word);
         Put (':');
         Put (Count, Width => 0);
         New_Line;
      end Process;

   begin
      M.Iterate (Process'Access);
   end;

end Count_Words;

package Scanners is
   pragma Pure;

   type Scanner (<>) is tagged limited private;

   function Scan (Line : String) return Scanner;

   function Has_Word (S : Scanner) return Boolean;
   function Word (S : Scanner) return String;

private

   type Handle (S : not null access Scanner) is limited null record;

   type Scanner (Last : Natural) is tagged limited record
      H          : Handle (Scanner'Access);
      Line       : String (1 .. Last);
      Word_First : Positive;
      Word_Last  : Natural;
   end record;

end Scanners;

with Ada.Characters.Latin_1;  use Ada.Characters;

package body Scanners is

   function Is_Whitespace (C : Character) return Boolean is
   begin
      case C is
         when ' ' | Latin_1.HT => 
            return True;
         when others =>
            return False;
      end case;
   end Is_Whitespace;
      

   procedure Next (S : in out Scanner) is
      I : Integer renames S.Word_First;
      J : Integer renames S.Word_Last;
      
   begin
      I := J + 1;
      while I <= S.Last 
        and then Is_Whitespace (S.Line (I))
      loop
         I := I + 1;
      end loop;
      
      if I > S.Last then
         return;  -- no more words on this line
      end if;
      
      J := I;
      while J < S.Last 
        and then not Is_Whitespace (S.Line (J + 1))
      loop
         J := J + 1;
      end loop;
   end Next;
      

   function Scan (Line : String) return Scanner is
   begin
      return S : Scanner (Line'Length) do
        S.Line := Line;
        -- S.Word_First := 1;
        S.Word_Last := 0;
        Next (S);
      end return;
   end Scan;


   function Has_Word (S : Scanner) return Boolean is
   begin
      return S.Word_First <= S.Word_Last;
   end Has_Word;


   function Word (S : Scanner) return String is
      L : constant Positive := S.Word_Last - S.Word_First + 1;
      
   begin
      return Result : String (1 .. L) do
        Result := S.Line (S.Word_First .. S.Word_Last);
        Next (S.H.S.all);
      end return;
   end Word;

end Scanners;



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

* Re: OO Style with Ada Containers
  2007-11-15  9:36       ` Ludovic Brenta
  2007-11-15 10:36         ` braver
@ 2007-11-19  2:36         ` Matthew Heaney
  1 sibling, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19  2:36 UTC (permalink / raw)


Ludovic Brenta <ludovic@ludovic-brenta.org> writes:

Instead of this:

   type Word_Counter is
      Word : Ada.Strings.Unbounded.Unbounded_String;
      Count : Natural;
   end Word_Counter;

I would have declared it something like this:

   type Word_Counter (Length : Positive) is record
      Word  : String (1 .. Length);
      Count : Natural;
   end record;

and then used the indefinite form of the (hashed) set.


>    Current_Word := Get_Next_Word;
>    Position := Counters.Find (Current_Word);
>    if Position = Word_Counter_Hashed_Sets.No_Element then
>       Counters.Insert (New_Item => (Word => Current_Word, Count => 1));
>    else
>       declare
>          E : constant Word_Counter := Counters.Element (Position);
>       begin
>          Counters.Replace_Element
>             (Position => Position,
>              New_Item => (Word => E.Word, -- [1]
>                           Counter => E.Counter + 1));
>       end;
>    end if;


Right, but this suffers from the same problem as in the original example (Find
duplicates the work done by Insert).


> (does [1] duplicate E.Word each time we increment the counter?  

Yes, because this replaces the entire element; the old element will get
destroyed, and a new element created.


> If so,
> consider using
> Ada.Containers.Hashed_Sets.Generic_Keys.Update_Element_Preserving_Keys).

Well, almost.  That does indeed allow you to modify an element in-place, but it
must copy the key in order to verify that you didn't modify it, so it doesn't
really solve the problem.



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

* Re: OO Style with Ada Containers
  2007-11-15 10:36         ` braver
  2007-11-15 11:35           ` Ludovic Brenta
@ 2007-11-19  2:38           ` Matthew Heaney
  1 sibling, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19  2:38 UTC (permalink / raw)


braver <deliverable@gmail.com> writes:

> Can we iterate through all
> elements in a collection with solely prefix notation?

You can always use Iterate, as in the example I provided.  However, that
returns a cursor as its process parameter, so you'll still have to deference
the cursor (using traditional syntax) to get the word (key) and count (element).




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

* Re: OO Style with Ada Containers
  2007-11-15 11:35           ` Ludovic Brenta
  2007-11-15 13:50             ` braver
  2007-11-15 18:22             ` braver
@ 2007-11-19  2:39             ` Matthew Heaney
  2 siblings, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19  2:39 UTC (permalink / raw)


Ludovic Brenta <ludovic@ludovic-brenta.org> writes:

> However in the present case, I advise against iterating over any container.
> My small example uses only Find, Insert, and Replace_Element for each word in
> the input file; there is no iteration over a container.

But you'll need to iterate when you're finished scanning the input file.




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

* Re: OO Style with Ada Containers
  2007-11-15 13:50             ` braver
@ 2007-11-19  2:45               ` Matthew Heaney
  0 siblings, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19  2:45 UTC (permalink / raw)


braver <deliverable@gmail.com> writes:

> Back to your original example, why are Ordered_Maps less preferable
> than Hashed_Sets?

The hashed vs. ordered distinction would only matter if you have some
interesting order for keys, e.g. you want to iterate over the map in
alphabetical order (since the word is the key).

For this problem you can use a set or a map. In this case it's probably easiest
to use a map, but you might want to try it using a set instead, if just as an
exercise.


> My code maintains for each distinct word its overall count, and uses
> Replace_Element for updating the count -- my impression is each word is
> stored just once with that use of Ordered_Maps, no?

Right, each word (the key) is stored only once.


> Also, I don't need to give it a hash function.

Right -- sometimes synthesizing a (good) hash function is difficult, so it's
often easier to just use an ordered map.  But either hashed map or ordered map
would work here (I used a hashed map in my earlier post).


> What are the advantages of Hashed_Sets?

I don't think there are any advantages here to using a set instead of a map.




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

* Re: OO Style with Ada Containers
  2007-11-15 18:22             ` braver
  2007-11-15 20:18               ` Ludovic Brenta
@ 2007-11-19  2:47               ` Matthew Heaney
  1 sibling, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19  2:47 UTC (permalink / raw)


braver <deliverable@gmail.com> writes:

> It turned out this should be
>
> 	-- Count can be anything below due to our definition of Equivalent:
> 	Position := Counters.Find ((Word => Current_Word, Count => 0));
>
> -- which adds to the cumbersomeness of Hashed_Sets vs. Ordered_Maps.
> So what are the advantages?

Well, if you're going to use the (hashed) set, then you should also instantiate
the nested package Generic_Keys, which would allow you to say:

  Position := Find (Counters, Word);



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

* Re: OO Style with Ada Containers
  2007-11-15 20:18               ` Ludovic Brenta
@ 2007-11-19  2:48                 ` Matthew Heaney
  0 siblings, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19  2:48 UTC (permalink / raw)


Ludovic Brenta <ludovic@ludovic-brenta.org> writes:

> I think Find is much more efficient in a Hashed_Set than in an
> Ordered_Map because comparing hash values is more efficient than
> comparing Unbounded_Strings.

No, because you still have to computer the hash value.  Suppose you have long
words?


> And in the algorithm, we call Find for
> each word in the input.
>
> This applies to Insert, too, and we call Insert for every new word in
> the input.
>
> How about trying both solutions and benchmarking them?

I showed a way in my earlier post about how to eliminate the separate Find
call.



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

* Re: OO Style with Ada Containers
  2007-11-15  8:43 ` Dmitry A. Kazakov
  2007-11-15 14:04   ` Maciej Sobczak
@ 2007-11-19  2:50   ` Matthew Heaney
  1 sibling, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19  2:50 UTC (permalink / raw)


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

> OO is traditionally based on dynamic polymorphism. Ada containers follow
> STL design based on templates, i.e. static polymorphism. That isn't much
> OO.

But his question was about using distinguished-receiver syntax, not OOP per se.
Container types are tagged, so you can use prefix notation, so all is well.



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

* Re: OO Style with Ada Containers
  2007-11-15 14:04   ` Maciej Sobczak
@ 2007-11-19  2:53     ` Matthew Heaney
  2007-11-19 13:44       ` Maciej Sobczak
  0 siblings, 1 reply; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19  2:53 UTC (permalink / raw)


Maciej Sobczak <see.my.homepage@gmail.com> writes:

> Not much.

The container library was directly influenced by the container-part of the STL.


> I would even say that Ada.Containers is somewhere between the two
> without being able to really benefit from advantages of any approach.

But in Ada type extension can only be done when the type is tagged.


> In paricular, I miss the ability to work with iterators *alone*.

You mean algorithms?  Ada has other mechanisms, such as nested procedures and
downward closures, and the container library was designed to use the Ada
mechanisms.



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

* Re: OO Style with Ada Containers
  2007-11-19  2:53     ` Matthew Heaney
@ 2007-11-19 13:44       ` Maciej Sobczak
  2007-11-19 14:44         ` Martin
                           ` (2 more replies)
  0 siblings, 3 replies; 66+ messages in thread
From: Maciej Sobczak @ 2007-11-19 13:44 UTC (permalink / raw)


On 19 Lis, 03:53, Matthew Heaney <matthewjhea...@earthlink.net> wrote:

> The container library was directly influenced by the container-part of the STL.

And I will repeat that I don't see much influence there.

It is impossible to come up with infinite number of significantly
different container libraries, so in practice there will be
similarities between any two, even if chosen randomly.
Can you convince me that Ada.Containers is closer to STL than to Java
containers (for example)? If not, then why it is repeated so often
that Ada.Containers were influenced by STL? Do you by any chance find
something in C++ that is worth imitating? :-)

I don't claim that the designers of Ada.Containers didn't have STL in
mind when taking some decisions, but the essence [*] of STL just
didn't get there.

[*] I agree that the exact meaning of "essence" here can be
subjective.

> > In paricular, I miss the ability to work with iterators *alone*.
>
> You mean algorithms?

As well.

>  Ada has other mechanisms, such as nested procedures and
> downward closures, and the container library was designed to use the Ada
> mechanisms.

So how can I use these mechanisms to partition the sequence? How can I
move the top 10 (for the given comparator) elements to the beginning?
How can I sort the first 10 elements of the sequence, without wasting
time on sorting the remaining billion?

How can I use these mechanisms to make iterator adaptors? Consider a
filtering iterator that automatically skips unwanted (for the given
predicate) elements. Consider a virtual iterator that does not have
*any* container behind, but can serve as a sequence generator. And so
on.

I know that I can achieve all these in Ada (after spending some
weeks), but the solution is so far from the spirit of STL that talking
about influence is a bit overstated.

--
Maciej Sobczak * www.msobczak.com * www.inspirel.com



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

* Re: OO Style with Ada Containers
  2007-11-19 13:44       ` Maciej Sobczak
@ 2007-11-19 14:44         ` Martin
  2007-11-19 15:51         ` Matthew Heaney
  2007-11-19 16:19         ` Dmitry A. Kazakov
  2 siblings, 0 replies; 66+ messages in thread
From: Martin @ 2007-11-19 14:44 UTC (permalink / raw)


On Nov 19, 1:44 pm, Maciej Sobczak <see.my.homep...@gmail.com> wrote:
[snip]
> I don't claim that the designers of Ada.Containers didn't have STL in
> mind when taking some decisions, but the essence [*] of STL just
> didn't get there.
[snip]

I'm sure Matt is aware of what influenced *him* when he designed the
Ada.Containers! ;-)

I guess the original "Charles" library was closed to the C++ STL
containers than "Ada.Containers" ended up but you can (if you look)
follow the influence through.

Cheers
-- Martin



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

* Re: OO Style with Ada Containers
  2007-11-19 13:44       ` Maciej Sobczak
  2007-11-19 14:44         ` Martin
@ 2007-11-19 15:51         ` Matthew Heaney
  2007-11-19 17:33           ` Markus E L
  2007-11-19 21:29           ` Maciej Sobczak
  2007-11-19 16:19         ` Dmitry A. Kazakov
  2 siblings, 2 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19 15:51 UTC (permalink / raw)


On Nov 19, 8:44 am, Maciej Sobczak <see.my.homep...@gmail.com> wrote:
> On 19 Lis, 03:53, Matthew Heaney <matthewjhea...@earthlink.net> wrote:
>
> Can you convince me that Ada.Containers is closer to STL than to Java
> containers (for example)?

But the burden of proof is on you, to prove that the container library
is *not* closer to the C++ than it is to the Java containers!  (And
since I know C++ but not Java, such a proof would indeed be
interesting!)


> If not, then why it is repeated so often
> that Ada.Containers were influenced by STL?

You can read my original library proposal here:

http://home.earthlink.net/~matthewjheaney/charles/ai302.txt

As I stated then:

"This library API is modeled on the STL.  It has the same containers
as
the STL does, using the same container names and semantics.  If you
know
the STL already then you will instantly understand how this library
works.  It does not have any of the STL algorithms, but that's only
because I wanted to keep the API small (and not because it's not
possible to support STL-style algorithms -- it is).  The API described
here has exactly the minimum set of containers I believe all Ada
developers need, in exactly the form they need it."


> Do you by any chance find
> something in C++ that is worth imitating? :-)

Yes, of course: the STL.


> I don't claim that the designers of Ada.Containers didn't have STL in
> mind when taking some decisions, but the essence [*] of STL just
> didn't get there.

Well, the library is modeled on the STL.  There are necessarily
differences, because the languages are different, and my design
philosophy was (and is) to use Ada idioms where appropriate.


> >  Ada has other mechanisms, such as nested procedures and
> > downward closures, and the container library was designed to use the Ada
> > mechanisms.
>
> How can I use these mechanisms to make iterator adaptors?

A generic algorithm in Ada would look something like:

generic
   type Cursor is private;
   with function Next (C : Cursor) return Cursor is <>;
   with function Has_Element (C : Cursor) return Boolean is <>;
   ...
procedure Generic_Algorithm (C : Cursor);

You can instantiate this on the container types directly, e.g.

package Integer_Vectors is new Vectors (Integer);
use Integer_Vectors;

procedure Algorithm is new Generic_Algorithm (Cursor);

This instantiation will deliver every integer element in the vector.
An iterator adapter just means replacing the cursor operations for the
container with something else, e.g.

function Return_Odd_Only (C : Cursor) return Cursor is
  CC : Cursor := C;

begin
  while Has_Element (CC)
    and then Element (CC) rem 2 = 0
  loop
     Next (CC);
  end loop;
  return CC;
end Return_Odd_Only;

procedure Algorithm is
  new Generic_Algorithm
  (Cursor,
   Next => Return_Odd_Only,
   others => <>);  -- verify syntax

procedure Op (V : Vector) is
begin
   Algorithm (V.First);
end;


> Consider a
> filtering iterator that automatically skips unwanted (for the given
> predicate) elements.

See above for an example.


> Consider a virtual iterator that does not have
> *any* container behind, but can serve as a sequence generator. And so
> on.

But the generic algorithms depend only on a cursor as a generic formal
-- the algorithms aren't tied to containers directly (which was
Stepanov's great insight).  For example, let's use the algorithm above
with an array:

type Integer_Array is (Positive range <>) of Integer;
-- the "container" type

procedure Op (A : Integer_Array) is
   function Has_Element (J : Integer) return Boolean is
   begin
      return J <= A'Last;
   end;

   procedure Algorithm is
     new Generic_Algorithm
     (Cursor => Integer,
      Next   => Integer'Succ);

begin
   Algorithm (A'First);
end;




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

* Re: OO Style with Ada Containers
  2007-11-19 13:44       ` Maciej Sobczak
  2007-11-19 14:44         ` Martin
  2007-11-19 15:51         ` Matthew Heaney
@ 2007-11-19 16:19         ` Dmitry A. Kazakov
  2007-11-19 20:45           ` Maciej Sobczak
  2 siblings, 1 reply; 66+ messages in thread
From: Dmitry A. Kazakov @ 2007-11-19 16:19 UTC (permalink / raw)


On Mon, 19 Nov 2007 05:44:02 -0800 (PST), Maciej Sobczak wrote:

> Consider a virtual iterator that does not have
> *any* container behind, but can serve as a sequence generator. And so
> on.

An iterator always has a container behind (a class of containers actually).
If you generate just a sequence, where do you know the mapping of the
sequence onto the elements of a container? Take 2,4,6,8. Why do you think
that it is each second element? Nope, my container is defined over {2, 8,
7, pi, 1.3, 0}.

In fact you imply some properties of "containers with iterators." That in
effect defines a class of. In a manifestedly typed language (like Ada) such
things have to be declared before use.

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



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

* Re: OO Style with Ada Containers
  2007-11-19 15:51         ` Matthew Heaney
@ 2007-11-19 17:33           ` Markus E L
  2007-11-19 21:29           ` Maciej Sobczak
  1 sibling, 0 replies; 66+ messages in thread
From: Markus E L @ 2007-11-19 17:33 UTC (permalink / raw)



Matthew Heaney wrote:

> On Nov 19, 8:44 am, Maciej Sobczak <see.my.homep...@gmail.com> wrote:
>> On 19 Lis, 03:53, Matthew Heaney <matthewjhea...@earthlink.net> wrote:
>>
>> Can you convince me that Ada.Containers is closer to STL than to Java
>> containers (for example)?
>
> But the burden of proof is on you, to prove that the container library
> is *not* closer to the C++ than it is to the Java containers!  (And
> since I know C++ but not Java, such a proof would indeed be
> interesting!)


God, the problems you got, people. Which kind of metric are you
proposing to measure "closer"?

Regards -- Markus




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

* Re: OO Style with Ada Containers
  2007-11-19 16:19         ` Dmitry A. Kazakov
@ 2007-11-19 20:45           ` Maciej Sobczak
  2007-11-20  2:24             ` Matthew Heaney
  2007-11-20  9:06             ` Dmitry A. Kazakov
  0 siblings, 2 replies; 66+ messages in thread
From: Maciej Sobczak @ 2007-11-19 20:45 UTC (permalink / raw)


On 19 Lis, 17:19, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:

> > Consider a virtual iterator that does not have
> > *any* container behind, but can serve as a sequence generator. And so
> > on.
>
> An iterator always has a container behind (a class of containers actually).
> If you generate just a sequence, where do you know the mapping of the
> sequence onto the elements of a container?

Why should I bother with mapping the sequence onto the container if
there is no container? There is no container, only a sequence.

> Take 2,4,6,8.

Got it!

> Why do you think
> that it is each second element?

This is not each second element. This is a sequence 2,4,6,8 (but it
really does not make any difference).

Now consider an iterator generating a (samples of) sine wave with
given parameters. Infinitely! It plays a sound using attached DAC.

There is no container behind. Just a sequence.

--
Maciej Sobczak * www.msobczak.com * www.inspirel.com



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

* Re: OO Style with Ada Containers
  2007-11-19 15:51         ` Matthew Heaney
  2007-11-19 17:33           ` Markus E L
@ 2007-11-19 21:29           ` Maciej Sobczak
  2007-11-19 22:16             ` Matthew Heaney
  1 sibling, 1 reply; 66+ messages in thread
From: Maciej Sobczak @ 2007-11-19 21:29 UTC (permalink / raw)


On 19 Lis, 16:51, Matthew Heaney <mhea...@on2.com> wrote:

> > Can you convince me that Ada.Containers is closer to STL than to Java
> > containers (for example)?
>
> But the burden of proof is on you

No, because I'm not convinced either way. :-)

Ada.Containers can be compared to Java containers on the basis that
each container from Ada.Containers (except from Indefinite_XXX, which
are Ada-specific) has some analogous implementation in the java.util
package.
Then, considering the fact that elements in Ada.Containers cannot be
modified without naming the container in addition to providing the
cursor/iterator and this is different from both STL and Java (STL
dereferences iterators to l-values and Java is reference-oriented
anyway - in both cases iterators can be used to query as well as to
update elements), then I would say that Ada.Containers has a similar
"distance" to STL as it has to java.util.

This metrics of "distance" is of course flawed, but the above is as
good as anything else.


> As I stated then:
>
> "This library API is modeled on the STL.  It has the same containers
> as
> the STL does, using the same container names and semantics.

I see (except for Indefinite_XXX, which are Ada-specific), but that
still does not convince me. C++ does not currently have any hash
containers (the "original" STL and some third-party implementations
might have them, though) and it has one more very useful sequence:
deque. Plus some adaptors like stack or queue and priority_queue. Not
mentioning multimap and multiset. The ecosystem of containers is much
wider in C++.

No, I don't think it qualifies for "it has the same containers".
Rather "you might find similarities".

> If you
> know
> the STL already then you will instantly understand how this library
> works.

This is true.
Same if you come from Java. :-)

The point is that Vector, Doubly_Linked_List or Hashed_Map are not
names reserved for STL - these are basic CS concepts, known to
everybody and everywhere.
There is nothing "STLish" in them.

> It does not have any of the STL algorithms, but that's only
> because I wanted to keep the API small (and not because it's not
> possible to support STL-style algorithms -- it is).  The API described
> here has exactly the minimum set of containers I believe all Ada
> developers need, in exactly the form they need it."

I understand it.

> > Do you by any chance find
> > something in C++ that is worth imitating? :-)
>
> Yes, of course: the STL.

What about IOStreams?

Hey, we can even mix these two:

copy(my_vector.begin(),
     my_vector.end(),
     ostream_iterator<int>(cout, " "));

;-)


> Well, the library is modeled on the STL.  There are necessarily
> differences, because the languages are different, and my design
> philosophy was (and is) to use Ada idioms where appropriate.

I understand it.

I understand that you took your knowledge of STL and with this
knowledge in mind designed the Ada.Containers.

Now - if you came from Java instead, do you think you would have
designed something different? I doubt it. I'm convinced that by taking
Java containers (they call them collections, actually), cutting off
things here and there and bending everything to achieve idiomatic Ada
you would come to the same result.

That's why I claim that there is no STL flavor in Ada.Containers. It
might have been there as a motivator, but was lost in the cutting and
bending phase.


> > How can I use these mechanisms to make iterator adaptors?
>
> A generic algorithm in Ada would look something like:
>
> generic
>    type Cursor is private;
>    with function Next (C : Cursor) return Cursor is <>;
>    with function Has_Element (C : Cursor) return Boolean is <>;
>    ...
> procedure Generic_Algorithm (C : Cursor);

You mean: read-only algorithm.

What about modifying algorithms?
Ada.Containers.Vectors.Generic_Sorting shows the problem.


> An iterator adapter just means replacing the cursor operations for the
> container with something else, e.g.
>
> function Return_Odd_Only (C : Cursor) return Cursor is
>   CC : Cursor := C;
>
> begin
>   while Has_Element (CC)
>     and then Element (CC) rem 2 = 0
>   loop
>      Next (CC);
>   end loop;
>   return CC;
> end Return_Odd_Only;
>
> procedure Algorithm is
>   new Generic_Algorithm
>   (Cursor,
>    Next => Return_Odd_Only,
>    others => <>);  -- verify syntax

I like it. Really. It is not possible to do it in C++, the new classes
have to be composed with replaced operations.

--
Maciej Sobczak * www.msobczak.com * www.inspirel.com



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

* Re: OO Style with Ada Containers
  2007-11-19 21:29           ` Maciej Sobczak
@ 2007-11-19 22:16             ` Matthew Heaney
  2007-11-19 22:22               ` Matthew Heaney
  2007-11-20 14:11               ` Maciej Sobczak
  0 siblings, 2 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19 22:16 UTC (permalink / raw)


On Nov 19, 4:29 pm, Maciej Sobczak <see.my.homep...@gmail.com> wrote:
> Then, considering the fact that elements in Ada.Containers cannot be
> modified without naming the container in addition to providing the
> cursor/iterator and this is different from both STL and Java (STL
> dereferences iterators to l-values and Java is reference-oriented
> anyway - in both cases iterators can be used to query as well as to
> update elements), then I would say that Ada.Containers has a similar
> "distance" to STL as it has to java.util.

Yes, by design the container has to be named in any operation that
modifies its elements, but this does *not* imply that the generic
algorithm itself has to know anything about containers:

generic
  type Cursor is private;
  type ET is private;
  with procedure Add (C : Cursor; E : ET) is <>;
  with function Next (C : Cursor) return Cursor is <>;
  with function Has_Element (C : Cursor) return Boolean is <>;
procedure Generic_Algorithm
  (C : Cursor;
   E : ET);

You can see here that the algorithm does not name a container.  The
body looks like this:

procedure Generic_Algorithm
  (C : Cursor;
   E : ET)
is
   CC : Cursor := C;
begin
   while Has_Element (CC) loop
      Add (CC, E);
      CC := Next (CC);
   end loop;
end Generic_Algorithm;

Now let's instantiate using our integer vector container:

procedure Op (V : in out Integer_Vectors.Vector) is
  procedure Add (C : Cursor; I : Integer) is
     procedure Process (E : in out Integer) is
     begin
        E := E + I;
     end Process;
  begin
     V.Update_Element (C, Process'Access);
  end Add;

  procedure Algorithm is
    new Generic_Algorithm (Cursor, Integer);
begin
  Algorithm (V.First);
end Op;

The point of this example is to demonstrate that Ada provides
mechanisms (locally-declared subprograms) to bind the algorithm to the
container.


> I see (except for Indefinite_XXX, which are Ada-specific), but that
> still does not convince me.

Well, I'm in a very good position to know whether the Ada container
library was designed with the STL in mind!


> C++ does not currently have any hash
> containers (the "original" STL and some third-party implementations
> might have them, though)

No, hashed forms were added to the latest version of the C++ standard.


> > > Do you by any chance find
> > > something in C++ that is worth imitating? :-)
>
> > Yes, of course: the STL.
>
> What about IOStreams?
>
> Hey, we can even mix these two:
>
> copy(my_vector.begin(),
>      my_vector.end(),
>      ostream_iterator<int>(cout, " "));
>
> ;-)

Oh, yes, I should have mentioned the iostream library.  In Ada you
could say:

generic
  type ET is limited private;
  with procedure Process (E : ET) is <>;
  ...
procedure Generic_Copy (...);

procedure Op (V : Integer_Vectors.Vector) is
  procedure Process (E : Integer) is
  begin
     Integer_Text_IO.Put (E, Width => 0);
     Put (' ');
  end;
  procedure Copy is
    new Generic_Copy (Integer, Process);
begin
  Copy (V.First);
end Op;

;^)


> > A generic algorithm in Ada would look something like:
>
> You mean: read-only algorithm.

No, I meant "algorithm"; see the example above.


> What about modifying algorithms?
> Ada.Containers.Vectors.Generic_Sorting shows the problem.

There is no problem.  To bind a generic algorithm to a container
object (that needs to be modified), use a locally-declared subprogram.


> I like it. Really. It is not possible to do it in C++, the new classes
> have to be composed with replaced operations.

It shows that it can be done -- just differently from C++.  Vive la
difference!

-Matt



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

* Re: OO Style with Ada Containers
  2007-11-19 22:16             ` Matthew Heaney
@ 2007-11-19 22:22               ` Matthew Heaney
  2007-11-20 14:11               ` Maciej Sobczak
  1 sibling, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-19 22:22 UTC (permalink / raw)


On Nov 19, 5:16 pm, Matthew Heaney <mhea...@on2.com> wrote:
>
> Now let's instantiate using our integer vector container:

Oops!  That should be:

procedure Add_To_Each_Element
  (V : in out Integer_Vectors.Vector;
   I : Integer)
is
   procedure Add (C : Cursor; J : Integer) is
      procedure Process (E : in out Integer) is
      begin
         E := E + J;
      end Process;
   begin
      V.Update_Element (C, Process'Access);
   end Add;

   procedure Algorithm is
     new Generic_Algorithm (Cursor, Integer);
begin
   Algorithm (V.First, I);
end Add_To_Each_Element;


Alternatively you could say:

procedure Add_To_Each_Element
  (V : in out Integer_Vectors.Vector;
   I : Integer)
is
   procedure Add (C : Cursor; J : Integer) is
   begin
      V.Replace_Element (C, Element (C) + J);
   end Add;

   procedure Algorithm is
     new Generic_Algorithm (Cursor, Integer);
begin
   Algorithm (V.First, I);
end Add_To_Each_Element;



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

* Re: OO Style with Ada Containers
  2007-11-19 20:45           ` Maciej Sobczak
@ 2007-11-20  2:24             ` Matthew Heaney
  2007-11-20  9:06             ` Dmitry A. Kazakov
  1 sibling, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-20  2:24 UTC (permalink / raw)


Maciej Sobczak <see.my.homepage@gmail.com> writes:

> Now consider an iterator generating a (samples of) sine wave with
> given parameters. Infinitely! It plays a sound using attached DAC.
>
> There is no container behind. Just a sequence.

That's more or less the model used to implement the random number generator.
The Random function delivers one element at a time from a virtual stream.

If you needed to plug a generator instance into a generic algorithm, then you
could easily use an object adapter to convert from the generator interface to
the sequence (cursor) interface.



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

* Re: OO Style with Ada Containers
  2007-11-19 20:45           ` Maciej Sobczak
  2007-11-20  2:24             ` Matthew Heaney
@ 2007-11-20  9:06             ` Dmitry A. Kazakov
  2007-11-20 12:16               ` Georg Bauhaus
  1 sibling, 1 reply; 66+ messages in thread
From: Dmitry A. Kazakov @ 2007-11-20  9:06 UTC (permalink / raw)


On Mon, 19 Nov 2007 12:45:12 -0800 (PST), Maciej Sobczak wrote:

> On 19 Lis, 17:19, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
> wrote:
> 
>>> Consider a virtual iterator that does not have
>>> *any* container behind, but can serve as a sequence generator. And so
>>> on.
>>
>> An iterator always has a container behind (a class of containers actually).
>> If you generate just a sequence, where do you know the mapping of the
>> sequence onto the elements of a container?
> 
> Why should I bother with mapping the sequence onto the container if
> there is no container?

Because the sequence will be later used with a container. And not to
forget, a sequence itself is a container. It is an ordered set of elements.

> This is not each second element. This is a sequence 2,4,6,8 (but it
> really does not make any difference).

Of course it does. Because in an ordered set you can query for the next
element of. Is Succ (2) = 4?

You cannot "take" values as they are. There is no values without types of.
 
> Now consider an iterator generating a (samples of) sine wave with
> given parameters. Infinitely! It plays a sound using attached DAC.

> There is no container behind. Just a sequence.

This is a totally wrong analogy with many more things assumed, than just a
container.

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



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

* Re: OO Style with Ada Containers
  2007-11-20  9:06             ` Dmitry A. Kazakov
@ 2007-11-20 12:16               ` Georg Bauhaus
  2007-11-21 15:17                 ` Dmitry A. Kazakov
  0 siblings, 1 reply; 66+ messages in thread
From: Georg Bauhaus @ 2007-11-20 12:16 UTC (permalink / raw)


On Tue, 2007-11-20 at 10:06 +0100, Dmitry A. Kazakov wrote:
> On Mon, 19 Nov 2007 12:45:12 -0800 (PST), Maciej Sobczak wrote:

> > Now consider an iterator generating a (samples of) sine wave with
> > given parameters. Infinitely! It plays a sound using attached DAC.
> 
> > There is no container behind. Just a sequence.
> 
> This is a totally wrong analogy with many more things assumed, than just a
> container.

Technically, you need none of the predefined container objects.
Formalistically, you might construe a notion of container capturing
the fact that a generator needs to exist somewhere. But so what.

But what is wrong with just giving the generator an iteration
interface? (I think Matt has dropped a word or two about this.)





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

* Re: OO Style with Ada Containers
  2007-11-19 22:16             ` Matthew Heaney
  2007-11-19 22:22               ` Matthew Heaney
@ 2007-11-20 14:11               ` Maciej Sobczak
  2007-11-20 17:00                 ` Matthew Heaney
  2007-11-20 18:06                 ` Georg Bauhaus
  1 sibling, 2 replies; 66+ messages in thread
From: Maciej Sobczak @ 2007-11-20 14:11 UTC (permalink / raw)


On 19 Lis, 23:16, Matthew Heaney <mhea...@on2.com> wrote:

> > Then, considering the fact that elements in Ada.Containers cannot be
> > modified without naming the container in addition to providing the
> > cursor/iterator and this is different from both STL and Java (STL
> > dereferences iterators to l-values and Java is reference-oriented
> > anyway - in both cases iterators can be used to query as well as to
> > update elements), then I would say that Ada.Containers has a similar
> > "distance" to STL as it has to java.util.
>
> Yes, by design the container has to be named in any operation that
> modifies its elements, but this does *not* imply that the generic
> algorithm itself has to know anything about containers:

[excellent examples with local subprograms]

I see your point. These examples are very good.

So let me try to get this interesting discussion a bit further.

Two points:

1.
The most important part of STL is the notion of range-based iteration.
Every single algorithm that iterates over something gets a pair of
iterators denoting the range to be visited.

sort(v.begin(), v.end());

But why not:

vector<int>::iterator middle = v.begin() +
                               (v.end() - v.begin()) / 2;

sort(v.begin(), middle);
sort(middle, v.end());

And then why not doing it in paraller... ;-)

Sorting only the first N elements?
(let's assume there are at least N)

sort(v.begin(), v.begin() + N);

And so on.
Ada.Containers does not support anything like this. The only available
algorithms work on whole containers.
This is more similar to Java approach, which has a sort method for
sorting whole lists (however, users can have a list-like view on the
part of the container, but this is not a range-based iteration, rather
smart application of view-like containers - in any case, the focus is
on containers, not on ranges).

2.
Another important part of STL is the notion of iterator category.
Depending on the category, the iterator can support different sets of
operations. The most powerful is RandomAccessIterator, which allows to
arbitrarily jump around the sequence in constant time.
Iterator to the vector is a random access iterator, because vector
itself is inherently random-accessible. This is why I was able to do
the above arithmetics to initialize the iterator to the middle of the
vector. I would not be able to do it in the same way with linked
lists.
Categories also allow the algorithms to automatically select the most
optimal implementation, depending on the abilities of the given
iterators.

Nothing like this exists in Ada, where cursors just resemble this:

http://java.sun.com/j2se/1.5.0/docs/api/java/util/ListIterator.html#method_summary

The interfaces are not exactly equivalent, of course, but the
"paradigm" is preserved.
For example, skipping N elements in the vector requires going to the
vector, asking for index, doing computation on the index value and
getting the new cursor.

These are the two reasons that allow me to claim that Ada.Containers
are more similar to Java than to STL.
Ada supports the Java-like "paradigm" for containers and iteration.

In STL-like library I would expect range-based algorithms and
iterators that benefit from abilities of the underlying sequence.

--
Maciej Sobczak * www.msobczak.com * www.inspirel.com



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

* Re: OO Style with Ada Containers
  2007-11-20 14:11               ` Maciej Sobczak
@ 2007-11-20 17:00                 ` Matthew Heaney
  2007-11-20 17:17                   ` Matthew Heaney
  2007-11-20 21:13                   ` Maciej Sobczak
  2007-11-20 18:06                 ` Georg Bauhaus
  1 sibling, 2 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-20 17:00 UTC (permalink / raw)


On Nov 20, 9:11 am, Maciej Sobczak <see.my.homep...@gmail.com> wrote:
> On 19 Lis, 23:16, Matthew Heaney <mhea...@on2.com> wrote:
>
> 1.
> The most important part of STL is the notion of range-based iteration.
> Every single algorithm that iterates over something gets a pair of
> iterators denoting the range to be visited.
>
> sort(v.begin(), v.end());

But there's nothing that precludes that in Ada:

generic
  type Cursor is private;
  ...
procedure Generic_Algorithm (First, Back : Cursor);

You'd instantiate as follows:

procedure Op (V : Integer_Vectors.Vector) is
  procedure Algorithm is
    new Generic_Algorithm (Integer_Vectors.Cursor, ...);

  C1 : Cursor := ...;
  C2 : Cursor := ...;
begin
  Algorithm (First => C1, Back => C2);
end Op;

Here the algorithm begins at C1, and terminates when the cursor equals
C2.  You can use any cursor you like as the "back" cursor value (one
off-the-end of the sequence).

If you want to iterate over the entire range, use V.First as the First
cursor and Integer_Vectors.No_Element as the Back cursor.

However, I find that it's easier to just say:

generic
  type Cursor is private;
  function Has_Element (C : Cursor) return Boolean is <>;
  ...
procedure Generic_Algorithm (First : Cursor);

So if we want to iterate over all of the elements, we accept the
default for Has_Element (which is declared in the package itself):

procedure Op (V : Integer_Vectors.Vector) is
  procedure Algorithm is
    new Generic_Algorithm (Integer_Vectors.Cursor);

  C1 : Cursor := ...;
begin
  Algorithm (C1);
end Op;

If you want to iterate over a range you can say:

procedure Op (V : Integer_Vectors.Vector) is
  C2 : constant Cursor := ...;

  function Has_Element (C : Cursor) return Boolean is
  begin
     return C /= C2;  -- or whatever
  end;
  procedure Algorithm is
    new Generic_Algorithm (Integer_Vectors.Cursor);

  C1 : Cursor := ...;
begin
  Algorithm (C1);
end Op;

Here the locally declared Has_Element becomes the default, so the
iteration terminates when the cursor equals C2.

You don't have to do it that way; you could say:

procedure Op (V : Integer_Vectors.Vector) is
  function Predicate (C : Cursor) return Boolean is ...;
  procedure Algorithm is
    new Generic_Algorithm
   (Integer_Vectors.Cursor,
    Has_Element => Predicate);

  C1 : Cursor := ...;
begin
  Algorithm (C1);
end Op;


> But why not:
>
> vector<int>::iterator middle = v.begin() +
>                                (v.end() - v.begin()) / 2;
>
> sort(v.begin(), middle);
> sort(middle, v.end());
>
> And then why not doing it in paraller... ;-)

Unfortunately, the vector container in the Ada library doesn't have
arithmetic operators.  (I lobbied for them, but wasn't able to
convince the ARG of their necessity.)  However, you can synthesize
such operators using the vector operations To_Cursor and To_Index.  So
we can write your example in Ada like this:


procedure Op (V : in out Integer_Vectors.Vector) is
  I : Extended_Index := V.First_Index + Count_Type'Pos (V.Length / 2);
  Middle : Cursor := To_Cursor (V, I);

begin
  Sort(V.First, Middle);
  Sort(Middle, No_Element);
end Op;


> Sorting only the first N elements?
> (let's assume there are at least N)
>
> sort(v.begin(), v.begin() + N);
>
> And so on.

procedure Op (V : in out Integer_Vectors.Vector) is
  I : Extended_Index := V.First + N;
  C : Cursor := To_Cursor (V, I);
begin
  Sort (V.First, C);
end Op;


> Ada.Containers does not support anything like this. The only available
> algorithms work on whole containers.

Well, there are no "available" algorithms in the standard library
(excepting array-based sorting), but assuming you have your own
algorithms you can do it as I describe above.


> This is more similar to Java approach, which has a sort method for
> sorting whole lists (however, users can have a list-like view on the
> part of the container, but this is not a range-based iteration, rather
> smart application of view-like containers - in any case, the focus is
> on containers, not on ranges).

For a range of elements, you can use the two-cursor approach (which
describe a half-open range), or pass the termination condition as a
generic formal predicate operation.


> 2.
> Another important part of STL is the notion of iterator category.
> Depending on the category, the iterator can support different sets of
> operations. The most powerful is RandomAccessIterator, which allows to
> arbitrarily jump around the sequence in constant time.

Right, but in Ada the category is described in the generic formal
region:

generic
  type IT is <>;  -- means any integer type
  type DT is (<>);  -- means any discrete type
  type FT is digits <>;  -- means any floating pt type
  ... -- etc

A "random-access cursor" would be described like this:


generic
  type Cursor is private;
  with function "+" (L : Cursor; R : Count_Type'Base)
    return Cursor is <>;
  with function "-" (L, R : Cursor)
    return Count_Type'Base is <>;
  ...
procedure Generic_Algorithm (...);


> Iterator to the vector is a random access iterator, because vector
> itself is inherently random-accessible.
> This is why I was able to do
> the above arithmetics to initialize the iterator to the middle of the
> vector.

As you can in Ada.


> I would not be able to do it in the same way with linked
> lists.

Right.


> Categories also allow the algorithms to automatically select the most
> optimal implementation, depending on the abilities of the given
> iterators.

Well, you're comparing apples and oranges.  In Ada, if a generic
algorithm requires a random-access cursor, it imports the requisite
operations as generic formal parameters.


> Nothing like this exists in Ada, where cursors just resemble this:

False; see the examples above.


> In STL-like library I would expect range-based algorithms and
> iterators that benefit from abilities of the underlying sequence.

As would I; see above for a few ideas.



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

* Re: OO Style with Ada Containers
  2007-11-20 17:00                 ` Matthew Heaney
@ 2007-11-20 17:17                   ` Matthew Heaney
  2007-11-20 21:13                   ` Maciej Sobczak
  1 sibling, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-20 17:17 UTC (permalink / raw)


On Nov 20, 12:00 pm, Matthew Heaney <mhea...@on2.com> wrote:
>
> > Sorting only the first N elements?
> > (let's assume there are at least N)
>
> > sort(v.begin(), v.begin() + N);
>
> > And so on.
>
> procedure Op (V : in out Integer_Vectors.Vector) is
>   I : Extended_Index := V.First + N;
>   C : Cursor := To_Cursor (V, I);
> begin
>   Sort (V.First, C);
> end Op;

That should really be (assuming N has type Count_Type):

procedure Op (V : in out Integer_Vectors.Vector) is
  I : Extended_Index := V.First_Index + Count_Type'Pos (N);
  C : Cursor := To_Cursor (V, I);
begin
  Sort (V.First, C);
end Op;

Alternatively, you could say:

procedure Op (V : in out Integer_Vectors.Vector) is
  I : Extended_Index := V.First_Index + Count_Type'Pos (N);
  function Has_Element (C : Cursor) return Boolean is
  begin
     return To_Index (C) < I;
  end;
  procedure Sort is new Generic_Sort (..., Has_Element);
begin
  Sort (V.First);
end Op;



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

* Re: OO Style with Ada Containers
  2007-11-20 14:11               ` Maciej Sobczak
  2007-11-20 17:00                 ` Matthew Heaney
@ 2007-11-20 18:06                 ` Georg Bauhaus
  1 sibling, 0 replies; 66+ messages in thread
From: Georg Bauhaus @ 2007-11-20 18:06 UTC (permalink / raw)


On Tue, 2007-11-20 at 06:11 -0800, Maciej Sobczak wrote:

> Two points:
> 
> 1.
> The most important part of STL is the notion of range-based iteration.
...
> Ada.Containers does not support anything like this.

I think Ada containers do support range-based iteration.
In fact, the Floor and Ceiling operations of ordered maps
(similar to C++ STL's lower_bound() and upper_bound())
will give you a cursor, and the Cursor's interface includes
"/=" ...

>  The only available
> algorithms work on whole containers.

That, again, is the algorithm question, isn't it? You get two
cursors, do something with them. For example, feed them to
a generic sum. Some algorithms can be found in the Charles
library (<= AI302, <= Ada.Containers).

http://charles.tigris.org


> 2.
> Another important part of STL is the notion of iterator category.
> Depending on the category, the iterator can support different sets of
> operations. The most powerful is RandomAccessIterator, which allows to
> arbitrarily jump around the sequence in constant time.

This particular case can be handled using Vector's Extended_Index
subtype,
" because vector 
  itself is inherently random-accessible."
To the extent that Extended_Index does not establish iterator
categories.






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

* Re: OO Style with Ada Containers
  2007-11-20 17:00                 ` Matthew Heaney
  2007-11-20 17:17                   ` Matthew Heaney
@ 2007-11-20 21:13                   ` Maciej Sobczak
  2007-11-20 21:57                     ` Matthew Heaney
  2007-11-21  4:51                     ` Matthew Heaney
  1 sibling, 2 replies; 66+ messages in thread
From: Maciej Sobczak @ 2007-11-20 21:13 UTC (permalink / raw)


On 20 Lis, 18:00, Matthew Heaney <mhea...@on2.com> wrote:

> > On 19 Lis, 23:16, Matthew Heaney <mhea...@on2.com> wrote:
>
> > 1.
> > The most important part of STL is the notion of range-based iteration.
> > Every single algorithm that iterates over something gets a pair of
> > iterators denoting the range to be visited.
>
> > sort(v.begin(), v.end());
>
> But there's nothing that precludes that in Ada:
[...]

Right, but it's not there (in AARM).

This is probably where we actually disagree. When you say that
something is similar to STL, then I expect to *find* STL-like concept
and solutions around it, not that I *can* have them if I code them
myself.

I really appreciate the examples you gave, I have learned something
from them.
Still, the thing that bothers me is that I have not seen such examples
in neither "the" Ada book, nor in AARM itself (and not on this group
during the last two years). This is what builds the spirit of some
particular solution. I see that you can use Ada to achieve arbitrary
effect, but your examples are the first I seen written like this (you
might still argue that I haven't seen enough). I assume this is
because nobody actually uses Ada.Containers like this. If this is true
(and based on "the" Ada book, AARM and this group, this statement is
justified), then from my perspective the STL-like coding is not part
of the spirit and culture of Ada.Containers.

Similarly, I might say that I can have algorithms that work on whole
containers in C++:

template <class Container>
void sort(Container & c)
{
    sort(c.begin(), c.end());
}

but in practice nobody writes like that. It is definitely possible,
but not part of the culture.


> > Iterator to the vector is a random access iterator, because vector
> > itself is inherently random-accessible.
> > This is why I was able to do
> > the above arithmetics to initialize the iterator to the middle of the
> > vector.
>
> As you can in Ada.

You cannot do arithmetics with cursors. They don't have appropriate
operators and the examples you shown work with indices, not with
cursors. Cursors themselves can be only incremented and decremented.

In this regard Ada's cursors are closer to Java than to STL.


In any case, your examples are a good motivation for more learning.
Thank you for your patience. :-)

--
Maciej Sobczak * www.msobczak.com * www.inspirel.com



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

* Re: OO Style with Ada Containers
  2007-11-20 21:13                   ` Maciej Sobczak
@ 2007-11-20 21:57                     ` Matthew Heaney
  2007-11-21  4:51                     ` Matthew Heaney
  1 sibling, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-20 21:57 UTC (permalink / raw)


On Nov 20, 4:13 pm, Maciej Sobczak <see.my.homep...@gmail.com> wrote:
>
> You cannot do arithmetics with cursors. They don't have appropriate
> operators and the examples you shown work with indices, not with
> cursors. Cursors themselves can be only incremented and decremented.

Well, if it makes any difference you could write:

generic
  with package Vector_Types is
    new Ada.Containers.Vectors (<>);
  use Vector_Types;

  V : access constant Vector;  --verify this
  -- you could also try
  -- V : in Vector;

package Vector_Cursor_Operations is

  function "+" (C : Cursor; I : Index_Type'Base)
    return Cursor;

  function "-" (L, R : Cursor) return Index_Type'Base;

end Vector_Cursor_Operations;


package body Vector_Cursor_Operations is

  function "+" (C : Cursor; I : Index_Type'Base)
    return Cursor
  is
    J : Index_Type'Base;

  begin
    if Has_Element (C) then
       J := V.Last_Index + 1;
    else
       J := To_Index (C);
    end if;

    return To_Cursor (V, J + I);
  end "+";

  function "-" (L, R : Cursor) return Index_Type'Base is
  begin
    if Has_Element (L) then
       if Has_Element (R) then
          return To_Index (L) - To_Index (R);
       else
          return No_Index;  --?
       end if;
    elsif Has_Element (R) then
       return V.Last_Index + 1 - To_Index (R);
    else
       return No_Index;  --?
    end if;
  end "-";

end Vector_Cursor_Operations;

The semantics needed to be nailed down but that should give you the
general idea.  Then you can say:

procedure Op (V : Integer_Vectors.Vector) is
  package Cursor_Ops is
    new Vector_Cursor_Operations
   (Integer_Vectors,
    V'Access);  -- verify this
  use Cursor_Ops;

  Middle : constant Cursor :=
    V.First + (No_Element - V.First) / 2;

begin
  Sort (V.First, Middle);
  Sort (Middle, No_Element);
end Op;



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

* Re: OO Style with Ada Containers
  2007-11-20 21:13                   ` Maciej Sobczak
  2007-11-20 21:57                     ` Matthew Heaney
@ 2007-11-21  4:51                     ` Matthew Heaney
  2007-11-21  9:18                       ` Georg Bauhaus
  1 sibling, 1 reply; 66+ messages in thread
From: Matthew Heaney @ 2007-11-21  4:51 UTC (permalink / raw)


Maciej Sobczak <see.my.homepage@gmail.com> writes:

> You cannot do arithmetics with cursors. They don't have appropriate
> operators and the examples you shown work with indices, not with
> cursors. Cursors themselves can be only incremented and decremented.

Actually, I thought about this more and concluded it doesn't matter that much.
C++ requires a uniform interface to allow the instantiation to happen, because
of the way it binds operations (by name).  But in Ada you can build a type
adapter on-the-fly (that's the locally declared subprogram stuff, which you
must often do anyway), and furthermore the actual name can differ from the
formal.  So not having cursor-based arithmetic isn't such a great loss, since
you can always instantiate the algorithm using the index subtype instead of
using the cursor (as I showed earlier, to pass an array to a generic
algorithm).

Here's the first method using a package that synthesizes cursor-based
arithmetic operators:

   procedure Op (V : Vector) is
      package Cursor_Ops is
         new Vector_Cursor_Operations (Integer_Vectors, V'Access);
      use Cursor_Ops;
      
      procedure Sort is
         new Generic_Sort 
        (Cursor_Type => Cursor, 
         Element_Type => Integer, 
         Index_Type => Positive);

      M : Cursor := V.First + (No_Element - V.First) / 2;
   begin
      Sort (V.First, M);
      Sort (M, No_Element);
   end Op;


Here's the second method that uses the index subtype to instantiate the generic
sort algorithm:

   procedure Op2 (V : Vector) is
      function Element (I : Index_Type'Base) return Integer is
      begin
         return V.Element (I);
      end;
      procedure Sort is
         new Generic_Sort 
        (Cursor_Type => Integer'Base,  -- or possibly Extended_Index
         Element_Type => Integer,
         Index_Type => Positive);

      M : Extended_Index := V.First_Index + Count_Type'Pos (V.Length / 2);

   begin
      Sort (V.First_Index, M);
      Sort (M, V.First_Index + Count_Type'Pos (V.Length));
   end Op2;

It's not that much different.

If you feel strongly that vector cursors should support some kind of
arithmetic, then you might want to post a message to the ada-comment list so
that the request gets logged, and eventually put on the ARG agenda.

Cheers,
Matt


--STX
with Ada.Containers.Vectors; use Ada.Containers;

package Test_Vector_Operations is
   pragma Preelaborate;

   package Integer_Vectors is new Vectors (Positive, Integer);
   use Integer_Vectors;

   procedure Op (V : Vector);
   procedure Op2 (V : Vector);

end Test_Vector_Operations;

with Vector_Cursor_Operations;
with Generic_Sort;

package body Test_Vector_Operations is
   
   procedure Op (V : Vector) is
      package Cursor_Ops is
         new Vector_Cursor_Operations (Integer_Vectors, V'Access);
      use Cursor_Ops;
      
      procedure Sort is
         new Generic_Sort 
        (Cursor_Type => Cursor, 
         Element_Type => Integer, 
         Index_Type => Positive);

      M : Cursor := V.First + (No_Element - V.First) / 2;
   begin
      Sort (V.First, M);
      Sort (M, No_Element);
   end Op;
      
      
   procedure Op2 (V : Vector) is
      function Element (I : Index_Type'Base) return Integer is
      begin
         return V.Element (I);
      end;
      procedure Sort is
         new Generic_Sort 
        (Cursor_Type => Integer'Base,
         Element_Type => Integer,
         Index_Type => Positive);

      M : Extended_Index := V.First_Index + Count_Type'Pos (V.Length / 2);

   begin
      Sort (V.First_Index, M);
      Sort (M, V.First_Index + Count_Type'Pos (V.Length));
   end Op2;


end Test_Vector_Operations;


generic
   type Cursor_Type is private;
   type Element_Type is private;
   type Index_Type is (<>);
   with function Element (C : Cursor_Type) return Element_Type is <>;
   with function "+" (C : Cursor_Type; I : Index_Type'Base) return Cursor_Type is <>;
   with function "-" (L, R : Cursor_Type) return Index_Type'Base is <>;
procedure Generic_Sort (First, Back : Cursor_Type);
pragma Pure (Generic_Sort);



procedure Generic_Sort (First, Back : Cursor_Type) is
begin
   null;
end Generic_Sort;


with Ada.Containers.Vectors; use Ada.Containers;

generic
   with package Vector_Types is new Vectors (<>);
   use Vector_Types;

   V : access constant Vector;

package Vector_Cursor_Operations is
   pragma Preelaborate;

   function "+" (L : Cursor; R : Index_Type'Base) return Cursor;
   function "-" (L, R : Cursor) return Index_Type'Base;

end Vector_Cursor_Operations;


package body Vector_Cursor_Operations is

   function "+" (L : Cursor; R : Index_Type'Base) return Cursor is
      I : Index_Type'Base;

   begin
      if Has_Element (L) then
         I := To_Index (L);
      else
         I := V.Last_Index + 1;
      end if;
      I := I + R;
      return To_Cursor (V.all, I);
   end "+";

   function "-" (L, R : Cursor) return Index_Type'Base is
      I, J : Index_Type'Base;

   begin
      if Has_Element (L) then
         I := To_Index (L);
      else
         I := V.Last_Index + 1;
      end if;
      
      if Has_Element (R) then
         J := To_Index (R);
      else
         J := V.Last_Index + 1;
      end if;
      
      return I - J;
   end "-";
      

end Vector_Cursor_Operations;






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

* Re: OO Style with Ada Containers
  2007-11-21  4:51                     ` Matthew Heaney
@ 2007-11-21  9:18                       ` Georg Bauhaus
  2007-11-21 15:59                         ` Maciej Sobczak
  2007-11-21 22:25                         ` Jeffrey R. Carter
  0 siblings, 2 replies; 66+ messages in thread
From: Georg Bauhaus @ 2007-11-21  9:18 UTC (permalink / raw)


Matthew Heaney wrote:
> Maciej Sobczak <see.my.homepage@gmail.com> writes:
> 
>> You cannot do arithmetics with cursors. They don't have appropriate
>> operators and the examples you shown work with indices, not with
>> cursors. Cursors themselves can be only incremented and decremented.
> 
> Actually, I thought about this more and concluded it doesn't matter that much.
> C++ requires a uniform interface to allow the instantiation to happen, because
> of the way it binds operations (by name).  But in Ada you can build a type
> adapter on-the-fly (that's the locally declared subprogram stuff, which you
> must often do anyway), and furthermore the actual name can differ from the
> formal.  So not having cursor-based arithmetic isn't such a great loss, since
> you can always instantiate the algorithm using the index subtype instead of
> using the cursor (as I showed earlier, to pass an array to a generic
> algorithm).

At the other end of the argument is a hint from Code Complete
(McConnell 1993), adding heresy++

'Think of arrays as sequential structures. Some of the brightest people
 in computer science have suggested that arrays never be accessed
 randomly, but only sequentially (Mills and Linger 1986). Their argument
 is that random accesses in arrays are similar to random "gotos" in a
 program.' (p251)

Since Vectors "is specifically optimized for insertion and deletion at
the high end (the end with the higher index) of the container" (A.18.2)
following this advice will defeat the purpose of Vectors only partially.
;)   At least when used by average programmers (like me) who rarely
invent quicksort for slices and such.




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

* Re: OO Style with Ada Containers
  2007-11-20 12:16               ` Georg Bauhaus
@ 2007-11-21 15:17                 ` Dmitry A. Kazakov
  0 siblings, 0 replies; 66+ messages in thread
From: Dmitry A. Kazakov @ 2007-11-21 15:17 UTC (permalink / raw)


On Tue, 20 Nov 2007 13:16:52 +0100, Georg Bauhaus wrote:

> But what is wrong with just giving the generator an iteration
> interface? (I think Matt has dropped a word or two about this.)

There is nothing wrong with that. What was wrong is an assumption that it
may have no any interface at all.

Whether say that an iteration implements an interface of container
iteration, or else refers to a container which iteration interface the
iterator implements, is a technical issue of the design.

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



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

* Re: OO Style with Ada Containers
  2007-11-21  9:18                       ` Georg Bauhaus
@ 2007-11-21 15:59                         ` Maciej Sobczak
  2007-11-21 17:41                           ` Georg Bauhaus
  2007-11-21 22:25                         ` Jeffrey R. Carter
  1 sibling, 1 reply; 66+ messages in thread
From: Maciej Sobczak @ 2007-11-21 15:59 UTC (permalink / raw)


On 21 Lis, 10:18, Georg Bauhaus <rm.tsho+bauh...@maps.futureapps.de>
wrote:

> At the other end of the argument is a hint from Code Complete
> (McConnell 1993), adding heresy++
>
> 'Think of arrays as sequential structures. Some of the brightest people
>  in computer science have suggested that arrays never be accessed
>  randomly, but only sequentially (Mills and Linger 1986).

Good luck with sorting or binary search. :-)
Using arrays as maps can be tricky as well...

On the other hand, sequential access is more cache-friendly and
benefits from modern optimizations (prefetch and such) at the hardware
level.

> At least when used by average programmers (like me) who rarely
> invent quicksort for slices and such.

What about array-organized maps/dictionaries (note that the array
index might be an enumeration type as well)?
Looking something in the dictionary is not something exotic, I hope?

--
Maciej Sobczak * www.msobczak.com * www.inspirel.com



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

* Re: OO Style with Ada Containers
  2007-11-21 15:59                         ` Maciej Sobczak
@ 2007-11-21 17:41                           ` Georg Bauhaus
  0 siblings, 0 replies; 66+ messages in thread
From: Georg Bauhaus @ 2007-11-21 17:41 UTC (permalink / raw)


On Wed, 2007-11-21 at 07:59 -0800, Maciej Sobczak wrote:

> What about array-organized maps/dictionaries (note that the array
> index might be an enumeration type as well)?
> Looking something in the dictionary is not something exotic, I hope?

Not at all exotic, I am glad I can use arrays as maps
together with coverage rules for the index type.
(Let alone arrays of Boolean, mapped to wires; I can't think
of the benefits of sequential access to components in this
case.)

EnumMap is a nice (and somehow familiar...) addition to
recent Java BTW.

But then, array-as-map in Ada is probably not the juggling
with i and j that I guess the quoted authors have had in mind.





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

* Re: OO Style with Ada Containers
  2007-11-21  9:18                       ` Georg Bauhaus
  2007-11-21 15:59                         ` Maciej Sobczak
@ 2007-11-21 22:25                         ` Jeffrey R. Carter
  1 sibling, 0 replies; 66+ messages in thread
From: Jeffrey R. Carter @ 2007-11-21 22:25 UTC (permalink / raw)


Georg Bauhaus wrote:
> 
> 'Think of arrays as sequential structures. Some of the brightest people
>  in computer science have suggested that arrays never be accessed
>  randomly, but only sequentially (Mills and Linger 1986). Their argument
>  is that random accesses in arrays are similar to random "gotos" in a
>  program.' (p251)

Actually, Mills and Linger suggested that arrays and pointers never be used; 
that the only data structures in an application be stacks, queues, and sets. 
They argued that indices and pointers were the data equivalent of using goto in 
programming. The paper is "Data Structured Programming: Program
Design without Arrays and Pointers", /IEEE Transactions on Software 
Engineering/, 1986 Feb.

-- 
Jeff Carter
"Beyond 100,000 lines of code you
should probably be coding in Ada."
P. J. Plauger
26



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

* Re: OO Style with Ada Containers
  2007-11-19  2:24       ` Matthew Heaney
@ 2007-11-23 10:28         ` braver
  2007-11-23 13:29           ` Martin Krischik
                             ` (2 more replies)
  2007-11-23 22:25         ` braver
  2007-11-25 14:08         ` braver
  2 siblings, 3 replies; 66+ messages in thread
From: braver @ 2007-11-23 10:28 UTC (permalink / raw)


Matt -- thanks a million for your detailed answers and analysis of Ada
Containers usage!  This is in fact what's needed the most -- not a
just a dry ARM spec, but as examples.  Perhaps you and others can post
a bunch of code somewhere with the containers usage?  That would be
most instructive.

A few questions about your solution:

--STX

-- I sense this allows to unroll a blob of Ada compilation units into
one unit per file, which tool reads this and does it?

What's the tradeoff between your solution, using

   package Map_Types is new Indefinite_Hashed_Maps
     (String,
      Natural,
      Hash_Case_Insensitive,
      Equal_Case_Insensitive);

-- and Ludivoc Brenta's, using Hashed_Sets of your modified
discriminated

   type Word_Counter (Length : Positive) is record
      Word  : String (1 .. Length);
      Count : Natural;
   end record;

In general, if I use lots of strings -- and my application area os
computational linguistics -- should I try to use plain String(1..N),
trying all kinds of tricks to constrain it as above, or
Ada.Strings.Unbounded are OK, too?

I've tried to leverage plain String, thinking that it being
unconstrained array can allow for behavior similar to dynamic strings
in Python, etc.  Alas, I cannot append to it doing S := S & Tail;...
OTOH, I can't index Unbounded string with US(i), -- or can I? -- and
it doesn't look pretty to use Element everywhere...  And if Element,
can that be well used with prefix notation?

Cheers,
Alexy



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

* Re: OO Style with Ada Containers
  2007-11-23 10:28         ` braver
@ 2007-11-23 13:29           ` Martin Krischik
  2007-11-23 14:19             ` Georg Bauhaus
  2007-11-25 13:38           ` Ludovic Brenta
  2007-11-26  3:55           ` Matthew Heaney
  2 siblings, 1 reply; 66+ messages in thread
From: Martin Krischik @ 2007-11-23 13:29 UTC (permalink / raw)


braver schrieb:

> Matt -- thanks a million for your detailed answers and analysis of Ada
> Containers usage!  This is in fact what's needed the most -- not a
> just a dry ARM spec, but as examples.  Perhaps you and others can post
> a bunch of code somewhere with the containers usage?  That would be
> most instructive. 

There had been a start on the wikibook:

http://en.wikibooks.org/wiki/Ada_Programming/Libraries/Ada.Containers
http://en.wikibooks.org/wiki/Ada_Programming/Libraries/Ada.Containers.Vectors

but not much happened there. But still, one can always add a "bunch of
code" there.

Martin

-- 
mailto://krischik@users.sourceforge.net
Ada programming at: http://ada.krischik.com



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

* Re: OO Style with Ada Containers
  2007-11-23 13:29           ` Martin Krischik
@ 2007-11-23 14:19             ` Georg Bauhaus
  0 siblings, 0 replies; 66+ messages in thread
From: Georg Bauhaus @ 2007-11-23 14:19 UTC (permalink / raw)


Martin Krischik wrote:
> braver schrieb:

> There had been a start on the wikibook:
> 
> http://en.wikibooks.org/wiki/Ada_Programming/Libraries/Ada.Containers
> http://en.wikibooks.org/wiki/Ada_Programming/Libraries/Ada.Containers.Vectors
> 
> but not much happened there. But still, one can always add a "bunch of
> code" there.

Right. The second part is a bit clumsy in particular.
With holidays approaching, that might change; OTOH,
Matt's examples are his. If we could get a few of these
as a basis for a reworked chapter, that will be great!

And would you prefer sci-fi film titles, or stars and planets
over dried vegetables from a fairy tail used as illustrative objects?





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

* Re: OO Style with Ada Containers
  2007-11-19  2:24       ` Matthew Heaney
  2007-11-23 10:28         ` braver
@ 2007-11-23 22:25         ` braver
  2007-11-23 22:46           ` Pascal Obry
  2007-11-26  4:03           ` Matthew Heaney
  2007-11-25 14:08         ` braver
  2 siblings, 2 replies; 66+ messages in thread
From: braver @ 2007-11-23 22:25 UTC (permalink / raw)


Very ineteresting -- Matt, can you pls elucidate these idioms below?

On Nov 19, 5:24 am, Matthew Heaney <matthewjhea...@earthlink.net>
wrote:

>    type Scanner (<>) is tagged limited private;

What does (<>) say here -- that the type is unconstrained?

> private
>
>    type Handle (S : not null access Scanner) is limited null record;
>
>    type Scanner (Last : Natural) is tagged limited record
>       H          : Handle (Scanner'Access);
>       Line       : String (1 .. Last);
>       Word_First : Positive;
>       Word_Last  : Natural;
>    end record;
>
> end Scanners;
>    function Scan (Line : String) return Scanner is
>    begin
>       return S : Scanner (Line'Length) do
>         S.Line := Line;
>         -- S.Word_First := 1;
>         S.Word_Last := 0;
>         Next (S);
>       end return;
>    end Scan;


>    function Word (S : Scanner) return String is
>       L : constant Positive := S.Word_Last - S.Word_First + 1;
>
>    begin
>       return Result : String (1 .. L) do
>         Result := S.Line (S.Word_First .. S.Word_Last);
>         Next (S.H.S.all);
>       end return;
>    end Word;

What's the logic behind the definition and usage of the Handle H
throughout?

Cheers,
Alexy



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

* Re: OO Style with Ada Containers
  2007-11-23 22:25         ` braver
@ 2007-11-23 22:46           ` Pascal Obry
  2007-11-23 22:52             ` braver
  2007-11-26  4:07             ` Matthew Heaney
  2007-11-26  4:03           ` Matthew Heaney
  1 sibling, 2 replies; 66+ messages in thread
From: Pascal Obry @ 2007-11-23 22:46 UTC (permalink / raw)
  To: braver

braver a �crit :
> Very ineteresting -- Matt, can you pls elucidate these idioms below?
> 
> On Nov 19, 5:24 am, Matthew Heaney <matthewjhea...@earthlink.net>
> wrote:
> 
>>    type Scanner (<>) is tagged limited private;
> 
> What does (<>) say here -- that the type is unconstrained?

Yes. Scanner has a privately defined discriminant. So the public view of
Scanner must be declared unconstrained.

>> private
>>
>>    type Handle (S : not null access Scanner) is limited null record;
>>
>>    type Scanner (Last : Natural) is tagged limited record
>>       H          : Handle (Scanner'Access);
>>       Line       : String (1 .. Last);
>>       Word_First : Positive;
>>       Word_Last  : Natural;
>>    end record;
>>
> 
> What's the logic behind the definition and usage of the Handle H
> throughout?

It is for gaining write access to function in parameter. A simpler
solution is:

    type Scanner (Last : Natural) is tagged limited record
       Self       : access Scanner := Scanner'Unchecked_Access;
       Line       : String (1 .. Last);
       Word_First : Positive;
       Word_Last  : Natural;
    end record;

Pascal.

-- 

--|------------------------------------------------------
--| Pascal Obry                           Team-Ada Member
--| 45, rue Gabriel Peri - 78114 Magny Les Hameaux FRANCE
--|------------------------------------------------------
--|              http://www.obry.net
--| "The best way to travel is by means of imagination"
--|
--| gpg --keyserver wwwkeys.pgp.net --recv-key C1082595



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

* Re: OO Style with Ada Containers
  2007-11-23 22:46           ` Pascal Obry
@ 2007-11-23 22:52             ` braver
  2007-11-26  4:09               ` Matthew Heaney
  2007-11-26  4:07             ` Matthew Heaney
  1 sibling, 1 reply; 66+ messages in thread
From: braver @ 2007-11-23 22:52 UTC (permalink / raw)


On Nov 24, 1:46 am, Pascal Obry <pas...@obry.net> wrote:
> braver a écrit :
>
> > Very ineteresting -- Matt, can you pls elucidate these idioms below?
>
> > On Nov 19, 5:24 am, Matthew Heaney <matthewjhea...@earthlink.net>
> > wrote:
>
> >>    type Scanner (<>) is tagged limited private;
>
> > What does (<>) say here -- that the type is unconstrained?
>
> Yes. Scanner has a privately defined discriminant. So the public view of
> Scanner must be declared unconstrained.
>
> >> private
>
> >>    type Handle (S : not null access Scanner) is limited null record;
>
> >>    type Scanner (Last : Natural) is tagged limited record
> >>       H          : Handle (Scanner'Access);
> >>       Line       : String (1 .. Last);
> >>       Word_First : Positive;
> >>       Word_Last  : Natural;
> >>    end record;
>
> > What's the logic behind the definition and usage of the Handle H
> > throughout?
>
> It is for gaining write access to function in parameter. A simpler
> solution is:
>
>     type Scanner (Last : Natural) is tagged limited record
>        Self       : access Scanner := Scanner'Unchecked_Access;
>        Line       : String (1 .. Last);
>        Word_First : Positive;
>        Word_Last  : Natural;
>     end record;

Ah.  Didn't see H assigned -- in this case, Scanner'Access with the
type name means the address of the actual parent type record instance?

So basically to simplify even further, we'd just have procedures with
honest in out parameters?

Cheers,
Alexy



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

* Re: OO Style with Ada Containers
  2007-11-23 10:28         ` braver
  2007-11-23 13:29           ` Martin Krischik
@ 2007-11-25 13:38           ` Ludovic Brenta
  2007-11-26  3:58             ` Matthew Heaney
  2007-11-26  3:55           ` Matthew Heaney
  2 siblings, 1 reply; 66+ messages in thread
From: Ludovic Brenta @ 2007-11-25 13:38 UTC (permalink / raw)


braver writes:
> In general, if I use lots of strings -- and my application area os
> computational linguistics -- should I try to use plain String(1..N),
> trying all kinds of tricks to constrain it as above, or
> Ada.Strings.Unbounded are OK, too?
> 
> I've tried to leverage plain String, thinking that it being
> unconstrained array can allow for behavior similar to dynamic
> strings in Python, etc.  Alas, I cannot append to it doing S := S &
> Tail;...  OTOH, I can't index Unbounded string with US(i), -- or can
> I? -- and it doesn't look pretty to use Element everywhere...

Unbounded_Strings are slower because they have append and insert
operations.  It is your decision whether to trade speed for these
features or not.  You can still append to a plain String by creating a
new String:

declare
   New_String : constant Word_Counter
                  (Length => Old_String.Length + 3,
                   Word => Old_String.Word & "...",
                   Count => Old_String.Count);
begin
   Map.Replace_Element (Position => ...,
                        New_Item => New_String);
end;

> And if Element, can that be well used with prefix notation?

No because Unbounded_String is not tagged, just like cursors.

-- 
Ludovic Brenta.



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

* Re: OO Style with Ada Containers
  2007-11-19  2:24       ` Matthew Heaney
  2007-11-23 10:28         ` braver
  2007-11-23 22:25         ` braver
@ 2007-11-25 14:08         ` braver
  2007-11-26  4:21           ` Matthew Heaney
  2 siblings, 1 reply; 66+ messages in thread
From: braver @ 2007-11-25 14:08 UTC (permalink / raw)


On Nov 19, 5:24 am, Matthew Heaney <matthewjhea...@earthlink.net>
wrote:
>    function Word (S : Scanner) return String is
>       L : constant Positive := S.Word_Last - S.Word_First + 1;
>
>    begin
>       return Result : String (1 .. L) do
>         Result := S.Line (S.Word_First .. S.Word_Last);
>         Next (S.H.S.all);
>       end return;
>    end Word;

I'm still pondering the workings of the Next (S.H.S.all) above.  Why
three (!) dots-dereferences?

Cheers,
Alexy



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

* Re: OO Style with Ada Containers
  2007-11-23 10:28         ` braver
  2007-11-23 13:29           ` Martin Krischik
  2007-11-25 13:38           ` Ludovic Brenta
@ 2007-11-26  3:55           ` Matthew Heaney
  2 siblings, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-26  3:55 UTC (permalink / raw)


braver <deliverable@gmail.com> writes:

> A few questions about your solution:
>
> --STX
>
> -- I sense this allows to unroll a blob of Ada compilation units into
> one unit per file, which tool reads this and does it?

gnatchop can extract the ada program units from a single text file.  Save the
post as a text file, remove everything up to (and including) the line "--STX",
and then run gnatchop on the resulting file.


> What's the tradeoff between your solution, using
>
>    package Map_Types is new Indefinite_Hashed_Maps
>      (String,
>       Natural,
>       Hash_Case_Insensitive,
>       Equal_Case_Insensitive);
>
> -- and Ludivoc Brenta's, using Hashed_Sets of your modified
> discriminated
>
>    type Word_Counter (Length : Positive) is record
>       Word  : String (1 .. Length);
>       Count : Natural;
>    end record;

It depends on whether you want to use a map or a set.  I don't see any
substantive difference here (well, I think a map is a more natural fit for your
problem), so if you're not sure then just use a map.

If you do use a set (again, try it, as it makes a nice exercise for learning
the library), then there's no reason to use Unbounded_String when a
discriminanted record will do (because the string itself never changes).


> In general, if I use lots of strings -- and my application area os
> computational linguistics -- should I try to use plain String(1..N),
> trying all kinds of tricks to constrain it as above, or
> Ada.Strings.Unbounded are OK, too?

I don't see any reason to use Unbouned_String with the container library, since
it includes indefinite forms allowing you to use type String directly.

It's not really an efficiency issue or anything, just the convenience of being
able to use type String directly without having to go through a secondary type
(Unbouned_String).


> I've tried to leverage plain String, thinking that it being
> unconstrained array can allow for behavior similar to dynamic strings
> in Python, etc.  

Well, that's what Unbounded_String is supposed to do.

If you have a string element, then an indefinite container will do just fine,
since you can always change the element.


> Alas, I cannot append to it doing S := S & Tail;...

No, not with a fixed length string (that's what it means for it to have a
constraint).

However, if this is a container element, then you can always use
Replace_Element to replace the string, e.g.

  M.Replace_Element (C, Element (C) & Tail);

There are other variations: Insert, Include, etc.


> OTOH, I can't index Unbounded string with US(i), -- or can I? -- 

You don't have an index operator, but you do have Element (to return a
character of the string) and Slice (to return a substring).


> and it doesn't look pretty to use Element everywhere...  And if Element, can
> that be well used with prefix notation?

If you're talking about type Unbounded_String, no, you can't use prefix
notation, since that type isn't publicly tagged.



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

* Re: OO Style with Ada Containers
  2007-11-25 13:38           ` Ludovic Brenta
@ 2007-11-26  3:58             ` Matthew Heaney
  0 siblings, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-26  3:58 UTC (permalink / raw)


Ludovic Brenta <ludovic@ludovic-brenta.org> writes:

> You can still append to a plain String by creating a
> new String:
>
> declare
>    New_String : constant Word_Counter
>                   (Length => Old_String.Length + 3,
>                    Word => Old_String.Word & "...",
>                    Count => Old_String.Count);
> begin
>    Map.Replace_Element (Position => ...,
>                         New_Item => New_String);
> end;

Something here isn't correct, since the Word_Counter subtype would only be used
for a set (although perhaps Map in your example has type Set), but also because
in the example the key should never change: only the associated count should
change (that's what Update_Element_Preserving_Key allows).



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

* Re: OO Style with Ada Containers
  2007-11-23 22:25         ` braver
  2007-11-23 22:46           ` Pascal Obry
@ 2007-11-26  4:03           ` Matthew Heaney
  2007-11-26 13:45             ` Matthew Heaney
  1 sibling, 1 reply; 66+ messages in thread
From: Matthew Heaney @ 2007-11-26  4:03 UTC (permalink / raw)


braver <deliverable@gmail.com> writes:

>>    type Scanner (<>) is tagged limited private;
>
> What does (<>) say here -- that the type is unconstrained?

Yes, this forces the type to have an initialization expression.  Here the type
is also limited, so that means must call one of the primitive operations
(loosely the "constructor" functions) that returns type Scanner; the only one I
defined in the example was operation Scan.

This is all a bit of a trick, since it allows me to put the storage for the
current line on the stack:

declare
  S : Scanner := Scan (Get_Line (F));
begin


> What's the logic behind the definition and usage of the Handle H
> throughout?

This is known as the "Rosen Trick".  It allows a function to modify its
argument (which you normally cannot do in Ada, since it doesn't allow in out
mode for function parameters).

Here I want function Word to return the current token on the line, and then
consume that token and advance to the next one.  You don't have to do it that
way, since you could always make the Next operation public.



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

* Re: OO Style with Ada Containers
  2007-11-23 22:46           ` Pascal Obry
  2007-11-23 22:52             ` braver
@ 2007-11-26  4:07             ` Matthew Heaney
  1 sibling, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-26  4:07 UTC (permalink / raw)


Pascal Obry <pascal@obry.net> writes:

> Yes. Scanner has a privately defined discriminant. So the public view of
> Scanner must be declared unconstrained.

Right, but that's not the reason I did it.  This is the "limited and
indefinite" idiom, to force the object to be initialized explicitly, using one
of the primitive operations defined for the type.


> It is for gaining write access to function in parameter. A simpler
> solution is:

I prefer Jean-Pierre's canonical technique (see the CLA archives from the fall
of '99 when the term "Rosen Trick" was coined), but your mileage might vary.



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

* Re: OO Style with Ada Containers
  2007-11-23 22:52             ` braver
@ 2007-11-26  4:09               ` Matthew Heaney
  0 siblings, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-26  4:09 UTC (permalink / raw)


braver <deliverable@gmail.com> writes:

> Ah.  Didn't see H assigned -- in this case, Scanner'Access with the
> type name means the address of the actual parent type record instance?

Right. The technical term is "current instance" of the type.


> So basically to simplify even further, we'd just have procedures with
> honest in out parameters?

Procedures already have that, but functions do not; hence the circumlocution.



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

* Re: OO Style with Ada Containers
  2007-11-25 14:08         ` braver
@ 2007-11-26  4:21           ` Matthew Heaney
  0 siblings, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-26  4:21 UTC (permalink / raw)


braver <deliverable@gmail.com> writes:

> I'm still pondering the workings of the Next (S.H.S.all) above.  Why
> three (!) dots-dereferences?

Because the mode for parameter S of function Word is in-mode, but the mode for
parameter of procedure Next is inout-mode.  The Rosen Trick is a clean way
(subject to certain constraints) to "cast away const".

(Try calling operation Next with parameter S directly -- what does the compiler
say?)

Here's how the Rosen Trick works:

S is a "constant view" of the scanner object.

S.H refers to the "handle" of the scanner object.

S.H.S.all refers to the discriminant of the handle, and the discriminant here
refers to the "current instance" of the same scanner object, but with a
"variable view" (that's why type Handle was declared with "access Scanner" as
the discriminant instead of "access constant Scanner").  An operation with a
"variable view" of an object can modify the state of the object.

So Word cannot directly modify its parameter S, since its parameter has only a
"constant view".  But S.H.S.all is a "variable view", so the parameter can be
modified indirectly (though the handle part of the object).

I know that's weird, but that's just the way it is (C++ is much more sensible
here, since a class can have non-const member functions).  As Robert Dewar puts
it, functions in Ada are allowed to modify their parameters -- they're just not
allowed to say they do!



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

* Re: OO Style with Ada Containers
  2007-11-26  4:03           ` Matthew Heaney
@ 2007-11-26 13:45             ` Matthew Heaney
  2007-11-26 19:09               ` braver
  0 siblings, 1 reply; 66+ messages in thread
From: Matthew Heaney @ 2007-11-26 13:45 UTC (permalink / raw)


Matthew Heaney <matthewjheaney@earthlink.net> writes:

> This is all a bit of a trick, since it allows me to put the storage for the
> current line on the stack:
>
> declare
>   S : Scanner := Scan (Get_Line (F));
> begin

Another possibility is:

  type Scanner (Line : not null access constant String) is 
    tagged limited private;
...

  declare
     L : aliased constant String := Get_Line (F);
     S : Scanner (L'Access);
  begin




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

* Re: OO Style with Ada Containers
  2007-11-26 13:45             ` Matthew Heaney
@ 2007-11-26 19:09               ` braver
  2007-11-26 20:29                 ` Matthew Heaney
  0 siblings, 1 reply; 66+ messages in thread
From: braver @ 2007-11-26 19:09 UTC (permalink / raw)


On Nov 26, 4:45 pm, Matthew Heaney <matthewjhea...@earthlink.net>
wrote:
> Matthew Heaney <matthewjhea...@earthlink.net> writes:
> > This is all a bit of a trick, since it allows me to put the storage for the
> > current line on the stack:
>
> > declare
> >   S : Scanner := Scan (Get_Line (F));
> > begin
>
> Another possibility is:
>
>   type Scanner (Line : not null access constant String) is
>     tagged limited private;
> ...
>
>   declare
>      L : aliased constant String := Get_Line (F);
>      S : Scanner (L'Access);
>   begin

So in this case Handle goes away altogether?



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

* Re: OO Style with Ada Containers
  2007-11-26 19:09               ` braver
@ 2007-11-26 20:29                 ` Matthew Heaney
  2007-11-27 19:31                   ` Georg Bauhaus
  0 siblings, 1 reply; 66+ messages in thread
From: Matthew Heaney @ 2007-11-26 20:29 UTC (permalink / raw)


On Nov 26, 2:09 pm, braver <delivera...@gmail.com> wrote:
> On Nov 26, 4:45 pm, Matthew Heaney <matthewjhea...@earthlink.net>
> wrote:
>
> So in this case Handle goes away altogether?

It was intended only to demonstrate another way to declare the type
(at least, the public part).  Implementation issues are orthogonal.

You'd only need the Rosen Trick if you have a function that has side-
effect (as function Word in my original example).

Another possibility is:

   F : aliased File_Type;
   S : Scanner (F'Access);
begin

Another possibility is:

  procedure Get_Next (S : in out Scanner; Word : out
Unbounded_String);

Yet another possibility is:

  procedure Get_Next
    (S    : in out Scanner;
     Word : out String;
     Last : out Natural);

Or just:

   function Has_Word (S : Scanner) return Boolean;
   function Word (S : Scanner) return String;
   procedure Get_Next (S : in out Scanner);

or:

  function Get_Next (S : Scanner) return Boolean;
  function Word (S : Scanner) return String;

or how about this (perhaps simplest of all, since it hides explicit
loops):

generic
  with procedure Process (Word : String);
procedure Generic_Scan (File : File_Type);



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

* Re: OO Style with Ada Containers
  2007-11-26 20:29                 ` Matthew Heaney
@ 2007-11-27 19:31                   ` Georg Bauhaus
  2007-11-27 20:12                     ` Matthew Heaney
  0 siblings, 1 reply; 66+ messages in thread
From: Georg Bauhaus @ 2007-11-27 19:31 UTC (permalink / raw)


On Mon, 2007-11-26 at 12:29 -0800, Matthew Heaney wrote:

> generic
>   with procedure Process (Word : String);
> procedure Generic_Scan (File : File_Type);

Hm. Isn't a local variable together with a local function
modifying the local variable a viable option? There is no
'Access then, but only "access" in a logical sense. The
variable/constant is not passed to the function but still
visible and accessible to the function. One could even wrap
them both in the same local package. The package might not
establish coupling in a type, but nevertheless it establishes
coupling of things that belong together.





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

* Re: OO Style with Ada Containers
  2007-11-27 19:31                   ` Georg Bauhaus
@ 2007-11-27 20:12                     ` Matthew Heaney
  0 siblings, 0 replies; 66+ messages in thread
From: Matthew Heaney @ 2007-11-27 20:12 UTC (permalink / raw)


On Nov 27, 2:31 pm, Georg Bauhaus <rm.tsoh+bauh...@maps.futureapps.de>
wrote:
> On Mon, 2007-11-26 at 12:29 -0800, Matthew Heaney wrote:
> > generic
> >   with procedure Process (Word : String);
> > procedure Generic_Scan (File : File_Type);
>
> Hm. Isn't a local variable together with a local function
> modifying the local variable a viable option?

Yes, that local function would be the generic actual in my example.


> There is no
> 'Access then, but only "access" in a logical sense. The
> variable/constant is not passed to the function but still
> visible and accessible to the function.

Yes, of course.


> One could even wrap
> them both in the same local package. The package might not
> establish coupling in a type, but nevertheless it establishes
> coupling of things that belong together.

I'm not sure I was clear here.  I meant:

package Scanner is
  generic
     with procedure Process (Word : String);
  procedure Generic_Scan (File : File_Type);
end Scanner;

Actually, in Ada05 you don't need the generic at all:

package Scanner is
  procedure Scan
    (File : File_Type,
     Process : not null access Process (Word : String));
end Scanner;

Then you could say:

declare
   M : Map;

   procedure Insert_Word (Word : String) is
      procedure Inc (Count : in out Natural) is
      begin
         Count := Count + 1;
      end;

      C : Cursor;
      B : Boolean;
   begin
      M.Insert (Word, 0, C, B);
      M.Update_Element (C, Inc'Access);
   end;

   F : File_Type;
begin
   Open (F, ...);
   Scanner.Scan (F, Insert_Word'Access);
   ... -- do something with map
end;



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

end of thread, other threads:[~2007-11-27 20:12 UTC | newest]

Thread overview: 66+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-11-14 23:28 OO Style with Ada Containers braver
2007-11-14 23:50 ` Adam Beneschan
2007-11-14 23:59   ` braver
2007-11-15  0:24     ` braver
2007-11-15  9:36       ` Ludovic Brenta
2007-11-15 10:36         ` braver
2007-11-15 11:35           ` Ludovic Brenta
2007-11-15 13:50             ` braver
2007-11-19  2:45               ` Matthew Heaney
2007-11-15 18:22             ` braver
2007-11-15 20:18               ` Ludovic Brenta
2007-11-19  2:48                 ` Matthew Heaney
2007-11-19  2:47               ` Matthew Heaney
2007-11-19  2:39             ` Matthew Heaney
2007-11-19  2:38           ` Matthew Heaney
2007-11-19  2:36         ` Matthew Heaney
2007-11-19  2:24       ` Matthew Heaney
2007-11-23 10:28         ` braver
2007-11-23 13:29           ` Martin Krischik
2007-11-23 14:19             ` Georg Bauhaus
2007-11-25 13:38           ` Ludovic Brenta
2007-11-26  3:58             ` Matthew Heaney
2007-11-26  3:55           ` Matthew Heaney
2007-11-23 22:25         ` braver
2007-11-23 22:46           ` Pascal Obry
2007-11-23 22:52             ` braver
2007-11-26  4:09               ` Matthew Heaney
2007-11-26  4:07             ` Matthew Heaney
2007-11-26  4:03           ` Matthew Heaney
2007-11-26 13:45             ` Matthew Heaney
2007-11-26 19:09               ` braver
2007-11-26 20:29                 ` Matthew Heaney
2007-11-27 19:31                   ` Georg Bauhaus
2007-11-27 20:12                     ` Matthew Heaney
2007-11-25 14:08         ` braver
2007-11-26  4:21           ` Matthew Heaney
2007-11-19  1:04   ` Matthew Heaney
2007-11-15  8:43 ` Dmitry A. Kazakov
2007-11-15 14:04   ` Maciej Sobczak
2007-11-19  2:53     ` Matthew Heaney
2007-11-19 13:44       ` Maciej Sobczak
2007-11-19 14:44         ` Martin
2007-11-19 15:51         ` Matthew Heaney
2007-11-19 17:33           ` Markus E L
2007-11-19 21:29           ` Maciej Sobczak
2007-11-19 22:16             ` Matthew Heaney
2007-11-19 22:22               ` Matthew Heaney
2007-11-20 14:11               ` Maciej Sobczak
2007-11-20 17:00                 ` Matthew Heaney
2007-11-20 17:17                   ` Matthew Heaney
2007-11-20 21:13                   ` Maciej Sobczak
2007-11-20 21:57                     ` Matthew Heaney
2007-11-21  4:51                     ` Matthew Heaney
2007-11-21  9:18                       ` Georg Bauhaus
2007-11-21 15:59                         ` Maciej Sobczak
2007-11-21 17:41                           ` Georg Bauhaus
2007-11-21 22:25                         ` Jeffrey R. Carter
2007-11-20 18:06                 ` Georg Bauhaus
2007-11-19 16:19         ` Dmitry A. Kazakov
2007-11-19 20:45           ` Maciej Sobczak
2007-11-20  2:24             ` Matthew Heaney
2007-11-20  9:06             ` Dmitry A. Kazakov
2007-11-20 12:16               ` Georg Bauhaus
2007-11-21 15:17                 ` Dmitry A. Kazakov
2007-11-19  2:50   ` Matthew Heaney
2007-11-19  1:03 ` Matthew Heaney

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