comp.lang.ada
 help / color / mirror / Atom feed
Search results ordered by [date|relevance]  view[summary|nested|Atom feed]
thread overview below | download mbox.gz: |
* Re: Unifont static compiled and stack size...
  @ 2023-08-14  9:39  4%       ` Dmitry A. Kazakov
  0 siblings, 0 replies; 132+ results
From: Dmitry A. Kazakov @ 2023-08-14  9:39 UTC (permalink / raw)


On 2023-08-14 11:25, Kevin Chadwick wrote:

>> Doing something like that for bitmap fonts is just as simple. The only 
>> minor issue is creating an index map: code point to the bitmap image 
>> name (array), because a flat array would blow out.
> 
> What does blow out mean in this context?

If you tried:

    type Font_Type is array (Code_Point) of Bitmap_Ptr;

The range of code points is 0..16#10FFFF#. E.g. when I implemented 
Ada.Strings.Maps for Unicode, I could not use such arrays either as the 
native ASCII implementation does.

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

^ permalink raw reply	[relevance 4%]

* wait does not perform as expected
@ 2023-02-22 16:34  6% Daniel Gaudry
  0 siblings, 0 replies; 132+ results
From: Daniel Gaudry @ 2023-02-22 16:34 UTC (permalink / raw)


hi
the following code :


with Gnat.Os_Lib;
with Ada.Strings;
with Ada.Strings.Fixed;
with Ada.Strings.Maps;
with Ada.Strings.Maps.Constants;
 with ada.text_io;
with Ada.Strings;


 procedure Hit_Return_To_Continue(Header     : in String   := "HIT RETURN TO CONTINUE";
                                    Mandatory  : in Boolean  := False;
                                    Skip_After : in Duration := 0.0)
      is

      Char  : Character := ' ';
      Hit   : Boolean   := True;
      Timer : Duration  := 0.0;

      begin

      -- ANYTHING TO DO ?
      if Mandatory
         then
          ada.text_io.Put(Header);

         -- ANY WAITING PERIOD TO DISPLAY ?
         if Skip_After > 0.0
            then

            -- KEEP THE USER'S ATTENTION
            while Timer < Skip_After loop
               Timer := 1.0 + @;
               delay 1.0;
               ada.text_io.Put(Natural(Skip_After - Timer)'Img);

               --USER ENDS THE WAITING PERIOD  BEFORE IT'S END ?


               TIO.LOOK_AHEAD(ITEM          => CHAR,
                              END_OF_LINE   => HIT);
               
                 ada.text_io.GET_IMMEDIATE(ITEM      => CHAR,
                                    AVAILABLE => HIT);
                  IF HIT THEN
                     RETURN;
                  END IF;

            end loop;

            -- USER WAITED FOR THE WHOLE  WAITING PERIOD
            -- LET HIM READ THE ZERO ON THE SCREEN

            delay 1.0;
            return;
         end if;

         Atio.Get_Immediate(Item      => Char,
                            Available => Hit);

         Atio.New_Line(Spacing => 1);

      end if;

   end Hit_Return_To_Continue;




the following call:

Hit_Return_To_Continue(Header        => "HIT RETURN TO CONTINUE",
                                           Mandatory  => true,
                                          Skip_After    => 5.0);

does not return if the user hits a key before the end of the countdown.

Can anybody help
Best regards

^ permalink raw reply	[relevance 6%]

* Re: Postcondition on Strings.Maps.To_Sequence
  2021-08-29  9:38  3% Postcondition on Strings.Maps.To_Sequence mockturtle
@ 2021-09-01 21:07  0% ` Stephen Leake
  0 siblings, 0 replies; 132+ results
From: Stephen Leake @ 2021-09-01 21:07 UTC (permalink / raw)


mockturtle <framefritti@gmail.com> writes:

>    pragma Assert (Edge.On_Input /= Null_Set);
>    pragma Assert (To_Sequence (Edge.On_Input)'Length > 0);
>
> where On_Input is a Character_Set (from Ada.Strings.Maps).
> SPARK accepts the first (that is, it can prove that On_Input is not
> empty), but complains that cannot prove the second (that is, that the
> same set converted to string can give an empty string).  

<snip>

I have used Spark some, but am not an expert.

So just guessing; does Spark actually understand 'Length?

For example, can it prove "a"'Length = 1?
and then To_Sequence (To_Set ('a'))'Length = 1?

> My question is: is this problem due to just a "weak" contract of
> To_Sequence or can actually To_Sequence return the empty string for some
> non Null_Set input?

My guess is neither; Spark is simply not smart enough yet. You'll have
to add some additional intermediate assertions in the body of
To_Sequence, especially one that relates the size of On_Input to the
size of the result string.

-- 
-- Stephe

^ permalink raw reply	[relevance 0%]

* Postcondition on Strings.Maps.To_Sequence
@ 2021-08-29  9:38  3% mockturtle
  2021-09-01 21:07  0% ` Stephen Leake
  0 siblings, 1 reply; 132+ results
From: mockturtle @ 2021-08-29  9:38 UTC (permalink / raw)


Dear.all,
in a code that I am trying to prove with SPARK I have the following two consecutive lines  [I am a beginner with SPARK and I am trying to learn... it is quite fun, if you have masochistic tendencies... ;-)] 

   pragma Assert (Edge.On_Input /= Null_Set);
   pragma Assert (To_Sequence (Edge.On_Input)'Length > 0);

where On_Input is a Character_Set (from Ada.Strings.Maps).
SPARK accepts the first (that is, it can prove that On_Input is not empty), but complains that cannot prove the second (that is, that the same set converted to string can give an empty string).  Actually, the contract of To_Sequence looks like 

function To_Sequence (Set : Character_Set) return Character_Sequence with
     Post =>
       (if Set = Null_Set then To_Sequence'Result'Length = 0)
          and then
       (for all Char in Character =>
          (if Is_In (Char, Set)
           then (for some X of To_Sequence'Result => Char = X)))
          and then
       (for all Char of To_Sequence'Result => Is_In (Char, Set))
          and then
       (for all J in To_Sequence'Result'Range =>
          (for all K in To_Sequence'Result'Range =>
             (if J /= K
              then To_Sequence'Result (J) /= To_Sequence'Result (K))));

and it shows clearly that if the input is Null_Set, then the output is the empty string, but does no explicit claim about the opposite case (if the input is not empty, then the output is not empty as well).

My question is: is this problem due to just a "weak" contract of To_Sequence or can actually To_Sequence return the empty string for some non Null_Set input?

^ permalink raw reply	[relevance 3%]

* Re: Advent of Code Day 6
  2020-12-06  8:39  4% Advent of Code Day 6 John Perry
@ 2020-12-06 11:07  0% ` Jeffrey R. Carter
  0 siblings, 0 replies; 132+ results
From: Jeffrey R. Carter @ 2020-12-06 11:07 UTC (permalink / raw)


On 12/6/20 9:39 AM, John Perry wrote:
> Today was quite easy, so I used the opportunity to learn about Ada.Strings.Maps, and that made for a much simpler solution to look at.
> 
> I do wonder about the efficiency, though. For instance, the only way I could find to count the number of elements in a Character_Set was by converting it to a Character_Sequence. Is there another way?

Probably one of the set pkgs in Ada.Containers or 
PragmARC.Data_Structures.Sets.Discrete might be a better choice than Character_Set

-- 
Jeff Carter
“[T]here are lots of people out there writing software
that should really be out cleaning toilets instead.”
Brian Catlin
173

^ permalink raw reply	[relevance 0%]

* Advent of Code Day 6
@ 2020-12-06  8:39  4% John Perry
  2020-12-06 11:07  0% ` Jeffrey R. Carter
  0 siblings, 1 reply; 132+ results
From: John Perry @ 2020-12-06  8:39 UTC (permalink / raw)


Today was quite easy, so I used the opportunity to learn about Ada.Strings.Maps, and that made for a much simpler solution to look at.

I do wonder about the efficiency, though. For instance, the only way I could find to count the number of elements in a Character_Set was by converting it to a Character_Sequence. Is there another way?

^ permalink raw reply	[relevance 4%]

* Re: CONSTRAINT ERROR? access check failed
  @ 2018-03-01 12:44  5%   ` Mehdi Saada
  0 siblings, 0 replies; 132+ results
From: Mehdi Saada @ 2018-03-01 12:44 UTC (permalink / raw)


Those are the two last things I would like you people to review. First, I can't get out of that loop, even with the exit INNER; after "Rentrez vos commandes". It starts it again.

INNER : loop
declare
   NOM_FICHIER : String := Get_Line;
   INDICE      : NATURAL := 0;
   begin
	if Index_Non_Blank (NOM_FICHIER) /= 0
	then
	    if not Exists (NOM_FICHIER) then Put_Line ("N'existe pas. Recommencez."); end if;
	    OPEN (FILE_ENTREE, In_File, NOM_FICHIER);
	    Set_Input (FILE_ENTREE);
	    while not End_Of_File loop
		INDICE := INDICE + 10;
		INSERT_OR_REPLACE (INDICE, LET_ONLY_GRAPHIC_CHARACTERS(GET_LINE));
	    end loop;
        end if;
	Put_Line ("Rentrer maintenant vos commandes"); exit INNER;
    exception when others => Put_Line ("ERREUR");
    end;
end loop INNER;

Then, could you tell what you think of that subprogram that is meant to purge a STRING from non graphic characters (those that make the program crash) ?

 function LET_ONLY_GRAPHIC_CHARACTERS
     (INPUT_STRING : in STRING) return STRING is
      use Ada.Strings.Maps.Constants,
	  Ada.Strings.Maps, Ada.Strings.Fixed, Ada.Strings;
      FIRST, I, COUNT, LAST : NATURal := INPUT_STRING'FIRST;
      OUTPUT_STRING         : STRING (INPUT_STRING'Range);

   begin
      loop
	 FIND_TOKEN (Source => INPUT_STRING (I .. INPUT_STRING'LAST),
	      Set    => Graphic_Set,
	      Test   => Inside ,
	      First  => First,
	      Last   => Last);
	 if Last in INPUT_STRING'Range and LAST /= 0 then
	    OUTPUT_STRING (I .. I + LAST - FIRST) := INPUT_STRING (FIRST .. LAST);
	    I := I + LAST - FIRST + 1;
	 else
	    exit; end if;
      end loop;
      PRAGMA Assert (Index (OUTPUT_STRING(OUTPUT_STRING'First .. 
			    (if I > OUTPUT_STRING'Length then OUTPUT_STRING'Last else I))
			      , GRAPHIC_SET, TEST => Outside) = 0, "CHARACTÈRES NON GRAPHIQUE ONT ECHAPPÉS !");
      return OUTPUT_STRING (OUTPUT_STRING'First .. (if I > OUTPUT_STRING'Length then OUTPUT_STRING'Last else I));
   end;


^ permalink raw reply	[relevance 5%]

* Re: Ada.Strings.Unbounded vs Ada.Containers.Indefinite_Holders
  @ 2017-09-23  9:16  5%           ` Jeffrey R. Carter
  0 siblings, 0 replies; 132+ results
From: Jeffrey R. Carter @ 2017-09-23  9:16 UTC (permalink / raw)


On 09/23/2017 10:09 AM, Dmitry A. Kazakov wrote:
> On 2017-09-23 00:15, Victor Porton wrote:
>>
>> In my opinion, it would be better to change RM phrasing from "null string"
>> to "empty string", because in some other languages (notably C) NULL means
>> something other. It is just confusing.
> 
> The adjective null and the noun null are distinct parts of speech. C's noun null 
> is an abbreviation of null pointer. If pointers can be null so strings can.

Another way to look at it: Ada has the formal concepts of:

* null access value ARM 4.2(9)
* null array 3.6.1(7)
* null constraint 3.2(7/2)
* null_exclusion 3.10(5.1/2)
* null extension 3.9.1(4.1/2)
* null procedure 6.7(3/3)
* null range 3.5(4)
* null record 3.8(15)
* null slice 4.1.2(7)
* null string literal 2.6(6)
* null value (of an access type) 3.10(13/2)
* null_statement 5.1(6)

not to mention the language-defined identifiers

Null_Address
    in System   13.7(12)
Null_Bounded_String
    in Ada.Strings.Bounded   A.4.4(7)
Null_Id
    in Ada.Exceptions   11.4.1(2/2)
Null_Occurrence
    in Ada.Exceptions   11.4.1(3/2)
Null_Ptr
    in Interfaces.C.Strings   B.3.1(7)
Null_Set
    in Ada.Strings.Maps   A.4.2(5)
    in Ada.Strings.Wide_Maps   A.4.7(5)
    in Ada.Strings.Wide_Wide_Maps   A.4.8(5/2)
Null_Task_Id
    in Ada.Task_Identification   C.7.1(2/2)
Null_Unbounded_String
    in Ada.Strings.Unbounded   A.4.5(5)

(Just look under N in the index.)

It's called overloading. Many of these cases refer to things that can have 
components and mean one with zero components: a null record has no components, a 
null array has no components ('Length = 0), a null string literal has no 
characters, a null set has no members, ... It should not be confusing.

-- 
Jeff Carter
"You cheesy lot of second-hand electric donkey-bottom biters."
Monty Python & the Holy Grail
14

^ permalink raw reply	[relevance 5%]

* Re: Question on bounded / unbounded strings
    2016-09-14 11:23  5% ` Arie van Wingerden
@ 2016-09-14 12:57  5% ` Arie van Wingerden
  1 sibling, 0 replies; 132+ results
From: Arie van Wingerden @ 2016-09-14 12:57 UTC (permalink / raw)


I finished the program.
It appears to be working correctly (only in Windows, because of the path 
separator).

Any comments to improve?

Code follows:
===========

with Ada.Text_Io;
with Ada.Environment_Variables;
with Ada.Strings.Fixed;
with Ada.Strings.Maps.Constants;

procedure Fip is

    package ATIO   renames Ada.Text_IO;
    package AEV    renames Ada.Environment_Variables;
    package ASF    renames Ada.Strings.Fixed;
    package ASMC renames Ada.Strings.Maps.Constants;

    Path   : string := ASF.Translate(AEV.Value("Path"), 
ASMC.Lower_Case_Map);
    Match : string := ASF.Translate(ATIO.Get_Line, ASMC.Lower_Case_Map);

    procedure FindMatch (Match : in string; Path : in string; StartPos : in 
positive; Len : in natural) is
        EndPos : positive;
    begin
        if Len > 0 then  -- Ignore case of an unnecessary semi colon
            EndPos := StartPos + Len - 1;
            if ASF.Index(Source => Path(StartPos .. EndPos), Pattern => 
Match) > 0 then
                ATIO.Put_Line(Path(StartPos .. EndPos));
            end if;
        end if;
    end FindMatch;

    procedure Match_Path (Match : in string; Path : in string) is
        StartPos : positive := 1;
        Len   : natural  := 0;
    begin
        for I in Path'Range loop
            if Path(I) = ';' then
                FindMatch(Match, Path, StartPos, Len);
                StartPos := I + 1;
                Len   := 0;
            else
                Len := Len + 1;
            end if;
        end loop;
    end Match_Path;

begin
    Match_Path(Match, Path);
    ATIO.Flush;
end Fip; 


^ permalink raw reply	[relevance 5%]

* Re: Question on bounded / unbounded strings
  @ 2016-09-14 11:23  5% ` Arie van Wingerden
  2016-09-14 12:57  5% ` Arie van Wingerden
  1 sibling, 0 replies; 132+ results
From: Arie van Wingerden @ 2016-09-14 11:23 UTC (permalink / raw)


Hi,
thank you *very* much. You are very helpful!

I created the following program, which only uses standard strings. It works 
partly.

There is one thing I cannot get to work properly:
    in the FOR loop the statement:
         ATIO.Put(Path(Start .. Len));
    outputs the first part of Path properly; but in the following cases it 
won't.
What am I doing wrong?

(Don't mind the matching; this is NOT correct currently).

(Wrongly indented pieces will be gone in final version.)

The program code (FIP stand for Find In Path):
======================================


with Ada.Text_Io;
    with Ada.Integer_Text_Io;
with Ada.Environment_Variables;
with Ada.Strings.Fixed;
with Ada.Strings.Maps.Constants;

procedure Fip is

    package ATIO   renames Ada.Text_IO;
package AITIO renames Ada.Integer_Text_Io;
    package AEV    renames Ada.Environment_Variables;
    package ASF    renames Ada.Strings.Fixed;
    package ASMC renames Ada.Strings.Maps.Constants;

    Path   : string := ASF.Translate(AEV.Value("Path"), 
ASMC.Lower_Case_Map);
    Match : string := ASF.Translate(ATIO.Get_Line, ASMC.Lower_Case_Map);

    procedure Match_Path (Match : in string; Path : in string) is
        Start : positive := 1;
        Len   : natural  := 0;
    begin
        for I in Path'Range loop
            if Path(I) = ';' then
ATIO.Put_Line("----------------------------------------------------");
ATIO.Put(Path(Start .. Len)); AITIO.Put(Start); AITIO.Put(Len); ATIO.Put(" 
"); ATIO.Put_Line(Match);
-- This matching part is not OK yet
                if Len > 0 and then Path(Start .. Len) = Match then
                    ATIO.Put_Line(Path(Start .. Len));
                end if;
                Start := I + 1;
                Len   := 0;
            else
                Len := Len + 1;
            end if;
        end loop;
    end Match_Path;

begin
    Match_Path(Match, Path);
    ATIO.Flush;
end Fip; 


^ permalink raw reply	[relevance 5%]

* How to check if letters are in a string?
@ 2015-07-18  9:00  5% Trish Cayetano
  0 siblings, 0 replies; 132+ results
From: Trish Cayetano @ 2015-07-18  9:00 UTC (permalink / raw)


Hi, 

How do you check if (exact number of) letters are in a string? 

1. This example should PASS because every letter is found in the string
LETTERS: HID
STRING:  HIDDEN

2. This example should FAIL because the letters contain 2 N's but the string only has 1 N. 
LETTERS: NINE
STRING:  HIDDEN


Pangram doesn't seem to be a solution... because it considers #2 above as PASS.
This is because pangrams check for AT LEAST one letter (this means, it considers a pangram even if the letter is a duplicate)


Is there another way how to check if (exact number of) letters are in a string? 
Thank you very much!


====
Here is the sample code: 

with Ada.Text_IO; use Ada.Text_IO;
with Ada.Strings.Maps; use Ada.Strings.Maps;
with Ada.Characters.Handling; use Ada.Characters.Handling;
procedure main is
 
	function ispangram(txt: String) return Boolean is
		lowtxt : String := To_Lower(txt);
		letset,txtset : Character_Set;
		begin
		letset := To_Set("nine");
		txtset := To_Set(lowtxt);
		return (letset-txtset)=Null_Set;
	end ispangram;
 
begin
put_line(Boolean'Image(ispangram("hidden")));

end main;

============================================
OUTPUT: 

C:\Users\a0284014\Desktop\ada\pangram\obj\main
TRUE

[2015-07-18 16:52:42] process terminated successfully, elapsed time: 00.37s

^ permalink raw reply	[relevance 5%]

* Re: OpenToken: Parsing Ada (subset)?
  2015-06-01 13:08  4% OpenToken: Parsing Ada (subset)? Jacob Sparre Andersen
@ 2015-06-02 22:12  3% ` Stephen Leake
  0 siblings, 0 replies; 132+ results
From: Stephen Leake @ 2015-06-02 22:12 UTC (permalink / raw)


Jacob Sparre Andersen <sparre@nbi.dk> writes:

> I'm attempting to use OpenToken to parse an Ada subset without much
> success.

(Shameless plug) An alternative approach is to start from the full Ada
grammar in Emacs ada-mode (ada-grammar.wy), and reduce it to what you
want. You'd also have to change the actions; they are focused on
supporting indentation and navigation in Emacs.

That grammar is in a .wy file, which must be processed by wisi-generate
to produce Ada code. The code produced by wisi-generate does not support
Ada actions at the moment (it only supports Emacs elisp, or a process or
dll communicating with Emacs), but you could either add that to
wisi-generate or treat the generated code as a template and add your own
actions. 

wisi-generate also assumes a single token type, so that changes how you
write the actions (more code in the actions, less in the tokens).

If you want to try adding actions to wisi-generate, I suggest you start
from FastToken (in monotone branch org.fasttoken, no release yet). It is
passing all its tests. I am still working on it, so the code will be
changing quite a bit. I plain to completely eliminate the token type
hierarchy, to avoid the run-time dynamic memory management it requires.
But that should be mostly orthogonal to actions. I'd be happy to help
with this; it is on my list of things to do someday, and having an
actual user is fun :).

> Identifier_T          =>
>    Tokenizer.Get (OpenToken.Recognizer.Identifier.Get
>                   (Start_Chars => Ada.Strings.Maps.Constants.Letter_Set,
>                    Body_Chars  => Ada.Strings.Maps.Constants.Alphanumeric_Set)),

This line says to use the default 'Get' routine to specify the token
type to use for Identifier_T; that is Master_Token.Instance, as you
complain later (see opentoken-token-enumerated-analyzer.ads:88). Change
to:

      Identifier_T          =>
         Tokenizer.Get 
            (OpenToken.Recognizer.Identifier.Get
                (Start_Chars => Ada.Strings.Maps.Constants.Letter_Set,
                 Body_Chars  => Ada.Strings.Maps.Constants.Alphanumeric_Set),
                 Identifiers.Get (Identifier_T),

I hate default parameters in general; this one is sort of convenient
(most terminals are happy being Master_Token.Instance, and you don't
have to repeat Identifier_T), but easily leads to this kind of bug (most
default parameters lead to hard to find bugs!).

Note that the ID parameter to Identifiers.Get could be defaulted; it is
overwritten in Analyzer.Initialize.

To see this in the code; terminal token objects are created on the
parser stack at opentoken-production-parser-lalr-parser.adb:318, as a
copy of a token returned by Analyzer.Get. Analyzer.Get returns the token
stored in the syntax; see opentoken-token-enumerated-analyzer.adb:772.

Nonterminal token objects are created at
opentoken-production-parser-lalr-parser.adb:177, as a copy of the
production left hand side (ie Dotted_Identifier below).

> Identifier : constant Identifiers.Instance'Class := Identifiers.Get (Identifier_T);
>
> I declare the grammar as:
>
>    Grammar : constant Production_List.Instance :=
>      Compilation_Unit  <= Dotted_Identifier & EOF and
>      Dotted_Identifier <= Dotted_Identifier & Dot & Identifier + Dotted_Identifiers.Join_Dotted_Identifiers and
>      Dotted_Identifier <= Identifier;

You might think that the use of Identifier.Instance here does what you
want, but it doesn't; the grammar determines the types only of the
nonterminals, the syntax determines the types of the terminals.

I suppose I should add that to the OpenToken user manual, but I'd rather
work on the FastToken user manual, which won't have this problem (only
one type for tokens :).

> I'm probably doing something obvious wrong, but what?

Obvious to me, but I've been messing with the lexer code in FastToken
recently; I switched to using regular expressions for the token
recognizers (to be closer to Aflex, which is also now supported). While
doing that, I deleted the default Get above.

Using regular expressions instead of the old OpenToken recognizers is a
big change, but wisi-generate takes care of most of the drudge work for
you (you just have to specify the actual regular expressions).

Glad to hear someone is using OpenToken, and it's fun to actually talk
about this stuff once in a while :).

-- 
-- Stephe


^ permalink raw reply	[relevance 3%]

* OpenToken: Parsing Ada (subset)?
@ 2015-06-01 13:08  4% Jacob Sparre Andersen
  2015-06-02 22:12  3% ` Stephen Leake
  0 siblings, 1 reply; 132+ results
From: Jacob Sparre Andersen @ 2015-06-01 13:08 UTC (permalink / raw)


I'm attempting to use OpenToken to parse an Ada subset without much
success.

I've reduced my problem all the way down to attempting to parse a
"dotted" identifier:

   Example           -> Dotted_Identifier EOF
   Dotted_Identifier -> Identifier | Dotted_Identifier "." Identifier

I declare the syntax like this (I've removed the reserved words for now):

   Syntax : constant Tokenizer.Syntax :=
     (Dot_T                 => Tokenizer.Get (OpenToken.Recognizer.Separator.Get (".")),
      Identifier_T          => Tokenizer.Get (OpenToken.Recognizer.Identifier.Get
                                                (Start_Chars => Ada.Strings.Maps.Constants.Letter_Set,
                                                 Body_Chars  => Ada.Strings.Maps.Constants.Alphanumeric_Set)),
      Comment_T             => Tokenizer.Get (OpenToken.Recognizer.Line_Comment.Get ("--")),
      Whitespace_T          => Tokenizer.Get (OpenToken.Recognizer.Character_Set.Get
                                                (OpenToken.Recognizer.Character_Set.Standard_Whitespace)),
      End_Of_File_T         => Tokenizer.Get (OpenToken.Recognizer.End_Of_File.Get));

I declare the token objects (for writing the grammar) like this:

   Dot        : constant Master_Token.Class := Master_Token.Get (Dot_T);
   EOF        : constant Master_Token.Class := Master_Token.Get (End_Of_File_T);
   Identifier : constant Identifiers.Instance'Class := Identifiers.Get (Identifier_T);

   Compilation_Unit  : constant Nonterminal.Class := Nonterminal.Get (Compilation_Unit_T);
   Dotted_Identifier : constant Dotted_Identifiers.Class := Dotted_Identifiers.Get (Dotted_Identifier_T);

I declare the grammar as:

   Grammar : constant Production_List.Instance :=
     Compilation_Unit  <= Dotted_Identifier & EOF and
     Dotted_Identifier <= Dotted_Identifier & Dot & Identifier + Dotted_Identifiers.Join_Dotted_Identifiers and
     Dotted_Identifier <= Identifier;

When I attempt to use this grammar to parse a "dotted" identifier, I run
into problems when OpenToken attempts to convert an identifier token to
a Dotted_Identifier.Instance object.  The problem which occurs is that
the identifier is represented as a plain Master_Token.Instance object,
which doesn't contain the actual identifier - which means that I can't
copy it into the "dotted" identifier.

I'm using OpenToken 6.0b.  The full compilable source (including the
used OpenToken packages) can be downloaded from
<http://jacob.sparre-andersen.dk/temp/ada_parsing_with_opentoken-2015-06-01-a.zip>.
To build the example:

   gnatmake parse_dotted_identifier

To test it:

   echo Ada.Text_IO.Integer_IO | ./parse_dotted_identifier

I'm probably doing something obvious wrong, but what?

Greetings,

Jacob
-- 
"It is very easy to get ridiculously confused about the
 tenses of time travel, but most things can be resolved
 by a sufficiently large ego."


^ permalink raw reply	[relevance 4%]

* Implementing character sets for Wide_Character
@ 2015-03-06 18:01  4% Martin Trenkmann
  0 siblings, 0 replies; 132+ results
From: Martin Trenkmann @ 2015-03-06 18:01 UTC (permalink / raw)


I need to implement a containment check for Wide_Character in a wide character set. I have two approaches in mind.

1. Using an array type similar to Ada.Strings.Maps.Character_Set.

   type Wide_Character_Set is array (Wide_Character) of Boolean with Pack;
   
   XYZ_Charset_Set : constant Wide_Character_Set
     := (Wide_Character'Val (100) .. Wide_Character'Val (900) => True,
         others                                               => False);

2. Using a function with a case statement.

   function Is_In_XYZ_Charset_Set (Item : Wide_Character) return Boolean is
   begin
      case Item is
         when Wide_Character'Val (100) .. Wide_Character'Val (900) => return True;
         when others                                               => return False;
      end case;
   end Is_In_XYZ_Charset_Set;


I know that using an array will consume more memory, but with the Pack aspect it should only be 8 KB - please correct me if I am wrong. The function approach is more memory friendly, but might be a bit slower as an array lookup.

Should I definitely avoid one of the solutions or is just a matter of available memory?

Thanks for your help.

Martin


^ permalink raw reply	[relevance 4%]

* Re: Practicalities of Ada for app development
  @ 2012-06-13  8:37  5%     ` Georg Bauhaus
  0 siblings, 0 replies; 132+ results
From: Georg Bauhaus @ 2012-06-13  8:37 UTC (permalink / raw)


On 13.06.12 02:04, Adam Beneschan wrote:

> Maybe this should be a challenge to the Ada community to come up with some common package specification (or set of packages) that would be sufficient to meet those needs, so that users wouldn't feel a need to switch to Perl to get the same kind of expressive power.  Offhand, I don't think it would need to become part of the official language standard (the letters I, S, and O are not a magical incantation that automatically makes software more trustworthy).  We've had working groups in the past that have developed standard packages that weren't part of the language (although some of them became part of later versions of the language, like Ada.Numerics).  What does anyone else think?  Does this seem worthwhile?  I have to admit, I've sometimes been frustrated when I need to work with text, although not enough to get me to use Perl for more than smallish programs, so off the top of my head this seems like it might be useful.

I like the "sufficient for most needs" part very much. It allows
going back to just regular languages.


This is my wishlist for a framework supporting regular languages
built around language features familiar to Ada programmers:

1. The building blocks in Ada.Strings.Maps, Ada.Strings.Maps.Constants
etc seem to correspond to character classes in POSIX REs:

   Hexadecimal_Digit_Set ~[0-9A-Fa-f]

Yet, the set operations of Maps exceed what I get in RE packages
of languages that start from version 7 regexp. Good!

So, alternation is presently possible for single characters.
Need groups and sequencing, expressed in the type system.

2. The container mechanics (Ada STL) offer one possible approach
to handling the set of matches:
The matching process results in an object of type that supports
iteration.  Perhaps not just Cursors, but also Extended_Index
like in Vectors, because programmers will expect that
groups in patterns are indexed by number.

3. The pattern matching facilities need not go beyond
regular languages. Provide some frequently used constant
patterns, such as end-of-line, start-of-string, word-boundary.

4. Add a single, read-only feature for RE inspection. It allows
observing the scanning process:

For example, given (ABC|BCD)E, and a function "&" returning
a pattern type,

   Alternation'(To_Set ("ABC") & To_Set ("BCD"))
      & To_Pattern ("E");

Here, it might be helpful to see the backtracking (if any) triggered
when the scanner is about to hit "E". Therefore, allow programmers
to implement an abstract pattern type that matches the empty
string. The scanner will call its primitive subprogram,
thus

   Alternation'(To_Set ("ABC") & To_Set ("BCD"))
     & user_defined_empty_1
     & To_Pattern ("E");

5. Define a small set of well chosen operators that reduce
verbosity.  (GNAT's Spitbol.Patterns has quite a lot of them.)

6. Producing new text from input text should not physically rely
on Ada.Strings.Unbounded. Instead, allocate new strings that can
clean up after themselves.


In conclusion, programmers would rely on Ada's type system when expressing
a pattern. They would not be forced to write in yet another macro
language in strings, as is required by most scripting languages.
Access to matched portions of input uses a familiar framework.



^ permalink raw reply	[relevance 5%]

* Re: Checking to see is a string is a letter
  @ 2012-04-03  7:09  6% ` Thomas Løcke
  0 siblings, 0 replies; 132+ results
From: Thomas Løcke @ 2012-04-03  7:09 UTC (permalink / raw)


On 04/03/2012 04:11 AM, deuteros wrote:
> Is there a way to check if a string variable contains a single letter?


A possible solution would be to take a look at Ada.Strings.Maps and
Ada.Strings.Maps.Constants.

You can then use Ada.Strings.Fixed.Count to count the number of matches
against your map, and if the result isn't exactly 1, then you know your
string contains either zero "single letter" or several "single letter".

But first of course you need to define exactly what "single letter"
means.

:o)

-- 
Thomas L�cke | thomas@12boo.net | http://12boo.net



^ permalink raw reply	[relevance 6%]

* Re: Passing C-style flags to C subprograms
  @ 2012-04-02 10:40  3%   ` Natasha Kerensikova
  0 siblings, 0 replies; 132+ results
From: Natasha Kerensikova @ 2012-04-02 10:40 UTC (permalink / raw)


Hello,

On 2012-03-30, Randy Brukardt <randy@rrsoftware.com> wrote:
> "Natasha Kerensikova" <lithiumcat@gmail.com> wrote in message 
> news:slrnjnbu7o.1lme.lithiumcat@sigil.instinctive.eu...
>> I have been trying to write an Ada binding to libevent2. There are all
>> sorts of issues and I have only started, so I'm not sure it will ever
>> lead to anything interesting, except for my own personal enlightenment.
>> One of these issues is passing and retrieving "C-style" flags, and I
>> would love to see sharing of insights on this topic.
> ...
>> I found a solution in Florist. I don't whether it's specific to Florist
>> or standard (I haven't been able to find a reference for POSIX for Ada).
>> It defines a private Option_Set type, which is actually a modular
>> integer, and operations on it implemented as bitwise arithmetic.
> ...
> This is essentilly what Claw does for (most) Windows flags.

Thanks a lot for sharing your experience. I was about to go for the
other solution, so you saved me the time to switch away from it when I
would have realized by myself that it had been a mistake.

One thing I still don't completely understand though is the choice of
">=" operator for testing output flags. Could you explain the rationale
behind it?

The only idea I have found it to consider flag type as representing
subsets of flags, and then consider ">=" as the equivalent of inclusion,
which is an order in the set of subsets. But in that case, wouldn't it
make more sense to use set-ish operators like "or" and "and" instead of
"+" and "-"?  Also "+" and "-" feel like operators on numbers, so having
a ">=" besides feels like an total order, while inclusion is only a
partial order.

Unless I'm missing something, that's the rational behind operators on
Ada.Strings.Maps.Character_Set. So I would have expected a Bit_Set or
Flag_Set (to include multi-bit flags) to have a similar interface. Why
isn't it so?



And as a side question, for situations when time efficiency is critical,
what are the ways to help a compiler use intrinsic operators for setting
and testing flags?

I guess publicly deriving specific flag types from Interfaces.C.unsigned
is a way to inherit implicit operators that are intrinsic, but then I
also allow operators that make no sense for a flag type, like "**" or
"/".

However, wouldn't hiding derivation in private part also turn public
operators into non-intrinsic operations?

And is there a way to allow "+" to be implemented with intrinsic "or" on
C.unsigned? If I understand 8.5.4.5 (from Ada 2005 RM) correctly,
renaming cannot do that. Or would a pragma Inline be enough to insert
the expression (with its private intrinsic "or") into the caller code
and end up with the same (assembly) result?

Or should all the above be just dismissed as premature optimization? (I
don't think so, because I believe it is never wrong to question, and
premature optimization is a wrong answer rather than a wrong question;
but I might be wrong).


Thanks again for your insights,
Natasha



^ permalink raw reply	[relevance 3%]

* Re: Need Help On Ada95 Problem
  @ 2012-02-10  8:47  6%   ` Simon Wright
  0 siblings, 0 replies; 132+ results
From: Simon Wright @ 2012-02-10  8:47 UTC (permalink / raw)


Shark8 <onewingedshark@gmail.com> writes:

>> Complete the function Encrypt(PIN) that takes a 4-digit PIN (as a
>> string) and returns the corresponding 4-letter code (also as a
>> string).
>>
>> Note: It would be possible to convert digits to letters using a giant
>> IF statement, but don't do this. Instead, the letter wheel is given to
>> you as a string, so use each digit to read the appropriate letter from
>> the string.
>
> Alright this is actually a simple problem; there are several ways to
> go about this,
> but let's play to Ada's strengths and use types.
>
> So start by describing things in terms of types.
>
>       Type Cypher_Character is Private;
>       Type Pin_Character is Private;
>
>       Type Pin_String is Array(1..4) of Pin_Character;

Really, this is overkill.

> Reading the problem the note says:
> It would be possible to convert digits to letters using a giant
> IF statement, but don't do this. Instead, the letter wheel is given to
> you as a string, so use each digit to read the appropriate letter from
> the string.
>
> Meaning that they're hinting strongly that you use the CASE statement.

No, they want you to use the encoding as an array.

But I think it would be better to use a character mapping:

   The_Ring : constant Ada.Strings.Maps.Character_Mapping
     := Ada.Strings.Maps.To_Mapping ("0123456789", "UROVALTINE");

   function Encode (PIN : String) return String
   is
   begin
      return Ada.Strings.Fixed.Translate (PIN, The_Ring);
   end Encode;

OK, if you encode 9537s you get ELVIs ...

But we don't know what the professor feels about students who are too
clever for their own good and have clearly been reading ahead in the
textbook! (or asking for help on the net ...)



^ permalink raw reply	[relevance 6%]

* Re: Why no Ada.Wide_Directories?
  @ 2011-10-18  8:01  6%       ` Dmitry A. Kazakov
  0 siblings, 0 replies; 132+ results
From: Dmitry A. Kazakov @ 2011-10-18  8:01 UTC (permalink / raw)


On Mon, 17 Oct 2011 16:47:49 -0700 (PDT), ytomino wrote:

> But other libraries in the standard are explicitly defined as Latin-1.
> It's certain that Ada.Character.Handling.To_Upper breaks UTF-8.
> So we can not use almost subprograms in Ada.Characters and Ada.Strings
> for handling file names.

Right, it is lot more than just Ada.Directories. I have implemented UTF-8
versions of Ada.Strings.Handling and Ada.Strings.Maps: sets and maps of
characters, case conversions, character characterization, superscript and
subscript integer I/O.

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



^ permalink raw reply	[relevance 6%]

* Re: An Example for Ada.Execution_Time
  @ 2010-12-29  3:10  4%   ` Randy Brukardt
  0 siblings, 0 replies; 132+ results
From: Randy Brukardt @ 2010-12-29  3:10 UTC (permalink / raw)


"BrianG" <briang000@gmail.com> wrote in message 
news:ifbi5c$rqt$1@news.eternal-september.org...
...
> I asked for:
>    >> An algorithm comparison program might look like:
>    >>
>    >> with Ada.Execution_Time ;
>    >> with Ada.Execution_Time.Timers ;
>    >Given the below program, please add some of the missing details to
>    >show how this can be useful without also "with Ada.Real_Time".
>    >Neither Execution_Time or Execution_Time.Timers provides any value
>    >that can be used directly.

This seems like a totally silly question. There are a lot of well-designed 
packages in Ada that don't do anything useful without at least one or more 
other packages. Indeed, if you consider "Standard" to be a separate package 
(and it is), there are hardly any packages that *don't* require some other 
package to be useful.

More to the point, you probably need Ada.IO_Exceptions to use 
Ada.Directories effectively (use of any package without error handling is 
toy use); Ada.Streams.Stream_IO require use of Ada.Streams (a separate 
package, which you will need separate use clauses for even if you get it 
imported automatically); Ada.Strings.Maps aren't useful for anything unless 
you combine them with one of the string handling packages, and so on.

Perhaps you would have been happier if Ada.Execution_Time had been a child 
of Ada.Real_Time (exactly as in the string case), but this wouldn't change 
anything.

The odd thing is that Duration is defined in Standard, rather than some more 
appropriate package. Giving this some sort of religious importance is beyond 
silly...

                                   Randy.





^ permalink raw reply	[relevance 4%]

* Re: ANN: Basil -- Internet Message (email) and MIME library for Ada v 1.0
  2008-07-24 19:13  6%                 ` Dmitry A. Kazakov
@ 2008-07-25 11:38  0%                   ` Alex R. Mosteo
  0 siblings, 0 replies; 132+ results
From: Alex R. Mosteo @ 2008-07-25 11:38 UTC (permalink / raw)


Dmitry A. Kazakov wrote:

> On Thu, 24 Jul 2008 18:53:07 +0200, Georg Bauhaus wrote:
> 
>> And XML/Ada's is not a Unicode library. Just some character
>> set transformations involving ISO10646 and others.
> 
> Strings edit provides UTF-8 support: sets, maps (similar to
> Ada.Strings.Maps), categorization, case conversions, wildcard matching etc
> 
>    http://www.dmitry-kazakov.de/ada/strings_edit.htm

Looks very interesting, thanks.

Incidentally, are you using some software to generate these webpages from
source code?



^ permalink raw reply	[relevance 0%]

* Re: ANN: Basil -- Internet Message (email) and MIME library for Ada v 1.0
  @ 2008-07-24 19:13  6%                 ` Dmitry A. Kazakov
  2008-07-25 11:38  0%                   ` Alex R. Mosteo
  0 siblings, 1 reply; 132+ results
From: Dmitry A. Kazakov @ 2008-07-24 19:13 UTC (permalink / raw)


On Thu, 24 Jul 2008 18:53:07 +0200, Georg Bauhaus wrote:

> And XML/Ada's is not a Unicode library. Just some character
> set transformations involving ISO10646 and others.

Strings edit provides UTF-8 support: sets, maps (similar to
Ada.Strings.Maps), categorization, case conversions, wildcard matching etc

   http://www.dmitry-kazakov.de/ada/strings_edit.htm

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



^ permalink raw reply	[relevance 6%]

* ANN: Some updates
@ 2008-03-30 17:13  5% Dmitry A. Kazakov
  0 siblings, 0 replies; 132+ results
From: Dmitry A. Kazakov @ 2008-03-30 17:13 UTC (permalink / raw)


Tables 1.8
http://www.dmitry-kazakov.de/ada/tables.htm

Strings Edit 2.1
http://www.dmitry-kazakov.de/ada/strings_edit.htm

Simple components 2.8
http://www.dmitry-kazakov.de/ada/components.htm

Fuzzy sets for Ada 5.2
http://www.dmitry-kazakov.de/ada/fuzzy.htm

The focus of these releases is UTF-8 support. New features include

Tables of case-insensitive tokes, UTF-8 encoded. Tables can be matched
against an UTF-8 encoded strings in order to get the longest alternative.
Chains of blank code points can be considered equivalent. Code points can
be ignored (hyphens, for example). Case equivalence is determined according
to the Unicode categories.

A fully functional UTF-8 substitute for Ada.Strings.Maps is provided. The
implementation is enhanced in order to support sets defined by an indicator
function additionally to a set of ranges.

An equivalent to Ada.Strings.Maps.Constants is provided as well.

Unicode code points characterization into all categories defined by the
standard.

Blocks of Unicode characters as defined in the standard.

The license is as always GM GPL.

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



^ permalink raw reply	[relevance 5%]

* Re: Range types
  2007-10-23 23:52  0%         ` anon
@ 2007-10-24 12:57  0%           ` Christos Chryssochoidis
  0 siblings, 0 replies; 132+ results
From: Christos Chryssochoidis @ 2007-10-24 12:57 UTC (permalink / raw)


Thanks very much, for giving me in such detail the solution, anon!

Regards,

Christos Chryssochoidis

anon wrote:
> --
> -- Package example:
> --
> -- For non Greek keyboards use Wide_Character 
> --  { ["<xxxx>"]["<yyyy>"] } 
> --  where <xxxx> and <yyyy> are 4-hex-digits to represents
> --  the two Wide_Character values 
> --
> --  Example is 
> --    ["03d6"]["1eee"]  -- valid Greek string
> --    ["03d6"]h -- is not valid because character "h" is not
> --                 a valid Greek character.
> --
> 
> 
> with Ada.Wide_Text_IO ;
> use  Ada.Wide_Text_IO ;
> 
> procedure tst is
> 
>   --
>   -- Internal Packages:
>   --
>   package Greek is
> 
> 
>     function Is_Greek_Character ( GC : Wide_Character ) 
>                                 return Boolean ;
> 
> 
>     function Is_Greek_Character_2 ( GC : Wide_Character ) 
>                                 return Boolean ;
> 
>     function Is_Greek_Character ( GS : Wide_String ) 
>                                 return Boolean ;
> 
>   end Greek ;
> 
>   --
>   -- Internal Body Package 
>   --
>   package body Greek is
> 
>     -- --------------------------- --
>     -- Use for Is_Greek_Character  --
>     -- --------------------------- --
> 
>     --
>     -- creates a greek constraint type
>     --
>     subtype Greek_Base is Wide_Character 
>                                 range Wide_Character'Val ( 16#370# )
>                                    .. Wide_Character'Val ( 16#1FFF# ) ;
> 
>     --
>     -- creates an excluded type
>     --
>     subtype Greek_Exclude_Subtype is Greek_Base
>                                 range Greek_Base'Val ( 16#03D8# )
>                                    .. Greek_Base'Val ( 16#0FFF# ) ;
> 
>     -- ----------------------------- --
>     -- Use for Is_Greek_Character_2  --
>     -- ----------------------------- --
> 
>     --
>     -- create lower greek characters type
>     --
>     subtype Lower_Greek_Character is Wide_Character 
>                                 range Wide_Character'Val ( 16#0370# )
>                                    .. Wide_Character'Val ( 16#03D7# ) ;
>     --
>     -- create upper greek characters type
>     --
>     subtype Upper_Greek_Character is Wide_Character 
>                                range Wide_Character 'Val ( 16#1000# )  
>                                   .. Wide_Character 'Val ( 16#1FFF# ) ;
> 
> 
> 
> 
>   --
>   -- Is_Greek_Character 
>   --
>   function Is_Greek_Character ( GC : Wide_Character ) 
>                               return Boolean is
> 
>     begin
>       --
>       -- Is character within the Greek base
>       --
>       if GC in Greek_Base then
>         --
>         -- Is character apart of the the non-Greek sub type
>         --
>         if GC in Greek_Exclude_Subtype then    
>           return False ;
>         else
>           return True ;
>         end if ;
>       else
>         return False ;
>       end if ;
>     end ;
> 
> 
>   --
>   -- Is_Greek_Character version number 2
>   --
>   function Is_Greek_Character_2 ( GC : Wide_Character ) 
>                               return Boolean is
> 
>     begin
>       --
>       -- Could use:
>       -- 
>       -- when Lower_Greek_Character | Upper_Greek_Character =>
>       --    return True ;
>       --
>       case GC is 
>          when Lower_Greek_Character =>
>             return True ;
>          when Upper_Greek_Character =>
>             return True ;
>          when others =>
>             return False ;
>       end case ;
>     end ;
> 
> 
>   function Is_Greek_Character ( GS : Wide_String ) 
>                               return Boolean is
> 
>     begin
>       --
>       -- Could use:
>       -- 
>       --
>       for Index in 1 .. GS'Length loop
>         --
>         -- if index-character of a string is not a Greek character
>         --
>         if not Is_Greek_Character_2 ( GS ( Index ) ) then 
>           return False ;
>         end if ;
>       end loop ;
>       --
>       -- String contains all Greek characters
>       --
>       return True ;
>     end ;
> 
>   end Greek ;
> 
> 
>   stz : wide_string ( 1..2 ) ;
> 
>   use Greek ;
> 
> begin
> --
>   put ( "Enter (2 character Greek string) => " ) ;
>   get ( stz ) ;
> --
>   put ( "Testing => " ) ;
>   put ( stz ) ;
>   new_line ;  
> --
>   if Is_Greek_Character ( stz ) then
>     put_line ( "Greek String ? => Yes" ) ;
>   else
>     put_line ( "Greek String ? => No" ) ;
>     --
>     -- Char 1 ?
>     --
>     if Is_Greek_Character ( stz ( 1 ) ) then
>       put_line ( "Character (1) Greek ? => Yes" ) ;
>     else
>       put_line ( "Character (1) Greek ? => No" ) ;
>     end if ;    
> 
>     --
>     -- Char 2 ?
>     --
>     if Is_Greek_Character_2 ( stz ( 2 ) ) then
>       put_line ( "Character (2) Greek ? => Yes" ) ;
>     else
>       put_line ( "Character (1) Greek ? => No" ) ;
>     end if ;
>   end if ;    
> --
> end tst ;
> 
> 
> 
> In <1193051690.350063@athprx04>, Christos Chryssochoidis <C.Chryssochoidis@gmail.com> writes:
>> Jacob Sparre Andersen wrote:
>>> Christos Chryssochoidis wrote:
>>>
>>>> I would like to define a subtype of Wide_Character for a program
>>>> that processes (unicode) text. This type would represent the Greek
>>>> letters.
>>> This sounds like what enumerated types are for.  You could do it like
>>> this:
>>>
>>>    type Faroese_Letter is ('a', 'A', 'b', 'B', 'd', 'D', 'ð', 'Ð',
>>>                            'e', 'E', [...],
>>>                            'y', 'Y', 'ý', 'Ý', 'æ', 'Æ', 'ø', 'Ø');
>>>    -- optional representation clause
>>>
>>>    function To_Wide_Wide_Character (Item : in Faroese_Letter)
>>>      return Wide_Wide_Character;
>>>
>>>    function To_Faroese_Letter (Item : in Wide_Wide_Character)
>>>      return Faroese_Letter;
>>>
>>> The conversion functions could make use of representation clauses,
>>> "Image" and "Value" functions, or tables.
>>>
>>>> Greek letters in Unicode, with all their diacritics, are
>>>> located in two separate ranges: 0370 - 03D7 and 1F00 - 1FFF. That's
>>>> 360 characters to write in an enumeration... Since gaps are not
>>>> allowed in ranges, I 'm thinking instead of defining such a type, to
>>>> define a function that would accept a Wide_Character as argument and
>>>> return a boolean value indicating whether the given Wide_Character
>>>> falls in the ranges of the Greek characters.
>>> This could be done very simply using Ada.Strings.Maps.
>>>
>>> How you should do it depends strongly on what you actually need your
>>> Greek_Letter type for.
>>>
>>> Greetings,
>>>
>>> Jacob
>> Thanks! Ada.Strings.Wide_Maps seems very helpful for what I want to do. 
>> Basically, what I would like to do is to write a program that given a 
>> text file in utf8 encoding, which would contain ancient greek text, 
>> which is written with all the diacritic marks on the letters, this 
>> program would load the contents of the file in memory, strip the 
>> in-memory text contents from all the diacritics except those used in 
>> today's "modern" Greek, and write the modified contents to a new file of 
>> the user's choosing. For this it would be nice if there were some 
>> package for regular expressions for Ada. Then if I succeeded in the 
>> mentioned task,  I 'd like to do some natural language processing (NLP, 
>> that is linguistics processing) with my program, but I don't know if Ada 
>> would be an appropriate language for such a task (NLP). I've seen on the 
>> web references to NLP applications with functional languages or logic 
>> programming languages, but not many implemented with imperative 
>> languages... (Sorry for getting of topic...)
>>
>> Thanks very much,
>> Christos
> 



^ permalink raw reply	[relevance 0%]

* Re: Range types
  2007-10-22 11:14  0%       ` Christos Chryssochoidis
@ 2007-10-23 23:52  0%         ` anon
  2007-10-24 12:57  0%           ` Christos Chryssochoidis
  0 siblings, 1 reply; 132+ results
From: anon @ 2007-10-23 23:52 UTC (permalink / raw)


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

--
-- Package example:
--
-- For non Greek keyboards use Wide_Character 
--  { ["<xxxx>"]["<yyyy>"] } 
--  where <xxxx> and <yyyy> are 4-hex-digits to represents
--  the two Wide_Character values 
--
--  Example is 
--    ["03d6"]["1eee"]  -- valid Greek string
--    ["03d6"]h -- is not valid because character "h" is not
--                 a valid Greek character.
--


with Ada.Wide_Text_IO ;
use  Ada.Wide_Text_IO ;

procedure tst is

  --
  -- Internal Packages:
  --
  package Greek is


    function Is_Greek_Character ( GC : Wide_Character ) 
                                return Boolean ;


    function Is_Greek_Character_2 ( GC : Wide_Character ) 
                                return Boolean ;

    function Is_Greek_Character ( GS : Wide_String ) 
                                return Boolean ;

  end Greek ;

  --
  -- Internal Body Package 
  --
  package body Greek is

    -- --------------------------- --
    -- Use for Is_Greek_Character  --
    -- --------------------------- --

    --
    -- creates a greek constraint type
    --
    subtype Greek_Base is Wide_Character 
                                range Wide_Character'Val ( 16#370# )
                                   .. Wide_Character'Val ( 16#1FFF# ) ;

    --
    -- creates an excluded type
    --
    subtype Greek_Exclude_Subtype is Greek_Base
                                range Greek_Base'Val ( 16#03D8# )
                                   .. Greek_Base'Val ( 16#0FFF# ) ;

    -- ----------------------------- --
    -- Use for Is_Greek_Character_2  --
    -- ----------------------------- --

    --
    -- create lower greek characters type
    --
    subtype Lower_Greek_Character is Wide_Character 
                                range Wide_Character'Val ( 16#0370# )
                                   .. Wide_Character'Val ( 16#03D7# ) ;
    --
    -- create upper greek characters type
    --
    subtype Upper_Greek_Character is Wide_Character 
                               range Wide_Character 'Val ( 16#1000# )  
                                  .. Wide_Character 'Val ( 16#1FFF# ) ;




  --
  -- Is_Greek_Character 
  --
  function Is_Greek_Character ( GC : Wide_Character ) 
                              return Boolean is

    begin
      --
      -- Is character within the Greek base
      --
      if GC in Greek_Base then
        --
        -- Is character apart of the the non-Greek sub type
        --
        if GC in Greek_Exclude_Subtype then    
          return False ;
        else
          return True ;
        end if ;
      else
        return False ;
      end if ;
    end ;


  --
  -- Is_Greek_Character version number 2
  --
  function Is_Greek_Character_2 ( GC : Wide_Character ) 
                              return Boolean is

    begin
      --
      -- Could use:
      -- 
      -- when Lower_Greek_Character | Upper_Greek_Character =>
      --    return True ;
      --
      case GC is 
         when Lower_Greek_Character =>
            return True ;
         when Upper_Greek_Character =>
            return True ;
         when others =>
            return False ;
      end case ;
    end ;


  function Is_Greek_Character ( GS : Wide_String ) 
                              return Boolean is

    begin
      --
      -- Could use:
      -- 
      --
      for Index in 1 .. GS'Length loop
        --
        -- if index-character of a string is not a Greek character
        --
        if not Is_Greek_Character_2 ( GS ( Index ) ) then 
          return False ;
        end if ;
      end loop ;
      --
      -- String contains all Greek characters
      --
      return True ;
    end ;

  end Greek ;


  stz : wide_string ( 1..2 ) ;

  use Greek ;

begin
--
  put ( "Enter (2 character Greek string) => " ) ;
  get ( stz ) ;
--
  put ( "Testing => " ) ;
  put ( stz ) ;
  new_line ;  
--
  if Is_Greek_Character ( stz ) then
    put_line ( "Greek String ? => Yes" ) ;
  else
    put_line ( "Greek String ? => No" ) ;
    --
    -- Char 1 ?
    --
    if Is_Greek_Character ( stz ( 1 ) ) then
      put_line ( "Character (1) Greek ? => Yes" ) ;
    else
      put_line ( "Character (1) Greek ? => No" ) ;
    end if ;    

    --
    -- Char 2 ?
    --
    if Is_Greek_Character_2 ( stz ( 2 ) ) then
      put_line ( "Character (2) Greek ? => Yes" ) ;
    else
      put_line ( "Character (1) Greek ? => No" ) ;
    end if ;
  end if ;    
--
end tst ;



In <1193051690.350063@athprx04>, Christos Chryssochoidis <C.Chryssochoidis@gmail.com> writes:
>Jacob Sparre Andersen wrote:
>> Christos Chryssochoidis wrote:
>> 
>>> I would like to define a subtype of Wide_Character for a program
>>> that processes (unicode) text. This type would represent the Greek
>>> letters.
>> 
>> This sounds like what enumerated types are for.  You could do it like
>> this:
>> 
>>    type Faroese_Letter is ('a', 'A', 'b', 'B', 'd', 'D', '�', '�',
>>                            'e', 'E', [...],
>>                            'y', 'Y', '�', '�', '�', '�', '�', '�');
>>    -- optional representation clause
>> 
>>    function To_Wide_Wide_Character (Item : in Faroese_Letter)
>>      return Wide_Wide_Character;
>> 
>>    function To_Faroese_Letter (Item : in Wide_Wide_Character)
>>      return Faroese_Letter;
>> 
>> The conversion functions could make use of representation clauses,
>> "Image" and "Value" functions, or tables.
>> 
>>> Greek letters in Unicode, with all their diacritics, are
>>> located in two separate ranges: 0370 - 03D7 and 1F00 - 1FFF. That's
>>> 360 characters to write in an enumeration... Since gaps are not
>>> allowed in ranges, I 'm thinking instead of defining such a type, to
>>> define a function that would accept a Wide_Character as argument and
>>> return a boolean value indicating whether the given Wide_Character
>>> falls in the ranges of the Greek characters.
>> 
>> This could be done very simply using Ada.Strings.Maps.
>> 
>> How you should do it depends strongly on what you actually need your
>> Greek_Letter type for.
>> 
>> Greetings,
>> 
>> Jacob
>
>Thanks! Ada.Strings.Wide_Maps seems very helpful for what I want to do. 
>Basically, what I would like to do is to write a program that given a 
>text file in utf8 encoding, which would contain ancient greek text, 
>which is written with all the diacritic marks on the letters, this 
>program would load the contents of the file in memory, strip the 
>in-memory text contents from all the diacritics except those used in 
>today's "modern" Greek, and write the modified contents to a new file of 
>the user's choosing. For this it would be nice if there were some 
>package for regular expressions for Ada. Then if I succeeded in the 
>mentioned task,  I 'd like to do some natural language processing (NLP, 
>that is linguistics processing) with my program, but I don't know if Ada 
>would be an appropriate language for such a task (NLP). I've seen on the 
>web references to NLP applications with functional languages or logic 
>programming languages, but not many implemented with imperative 
>languages... (Sorry for getting of topic...)
>
>Thanks very much,
>Christos




^ permalink raw reply	[relevance 0%]

* Re: Range types
  2007-10-22  7:23  4%     ` Jacob Sparre Andersen
@ 2007-10-22 11:14  0%       ` Christos Chryssochoidis
  2007-10-23 23:52  0%         ` anon
  0 siblings, 1 reply; 132+ results
From: Christos Chryssochoidis @ 2007-10-22 11:14 UTC (permalink / raw)


Jacob Sparre Andersen wrote:
> Christos Chryssochoidis wrote:
> 
>> I would like to define a subtype of Wide_Character for a program
>> that processes (unicode) text. This type would represent the Greek
>> letters.
> 
> This sounds like what enumerated types are for.  You could do it like
> this:
> 
>    type Faroese_Letter is ('a', 'A', 'b', 'B', 'd', 'D', '�', '�',
>                            'e', 'E', [...],
>                            'y', 'Y', '�', '�', '�', '�', '�', '�');
>    -- optional representation clause
> 
>    function To_Wide_Wide_Character (Item : in Faroese_Letter)
>      return Wide_Wide_Character;
> 
>    function To_Faroese_Letter (Item : in Wide_Wide_Character)
>      return Faroese_Letter;
> 
> The conversion functions could make use of representation clauses,
> "Image" and "Value" functions, or tables.
> 
>> Greek letters in Unicode, with all their diacritics, are
>> located in two separate ranges: 0370 - 03D7 and 1F00 - 1FFF. That's
>> 360 characters to write in an enumeration... Since gaps are not
>> allowed in ranges, I 'm thinking instead of defining such a type, to
>> define a function that would accept a Wide_Character as argument and
>> return a boolean value indicating whether the given Wide_Character
>> falls in the ranges of the Greek characters.
> 
> This could be done very simply using Ada.Strings.Maps.
> 
> How you should do it depends strongly on what you actually need your
> Greek_Letter type for.
> 
> Greetings,
> 
> Jacob

Thanks! Ada.Strings.Wide_Maps seems very helpful for what I want to do. 
Basically, what I would like to do is to write a program that given a 
text file in utf8 encoding, which would contain ancient greek text, 
which is written with all the diacritic marks on the letters, this 
program would load the contents of the file in memory, strip the 
in-memory text contents from all the diacritics except those used in 
today's "modern" Greek, and write the modified contents to a new file of 
the user's choosing. For this it would be nice if there were some 
package for regular expressions for Ada. Then if I succeeded in the 
mentioned task,  I 'd like to do some natural language processing (NLP, 
that is linguistics processing) with my program, but I don't know if Ada 
would be an appropriate language for such a task (NLP). I've seen on the 
web references to NLP applications with functional languages or logic 
programming languages, but not many implemented with imperative 
languages... (Sorry for getting of topic...)

Thanks very much,
Christos



^ permalink raw reply	[relevance 0%]

* Re: Range types
  @ 2007-10-22  7:23  4%     ` Jacob Sparre Andersen
  2007-10-22 11:14  0%       ` Christos Chryssochoidis
  0 siblings, 1 reply; 132+ results
From: Jacob Sparre Andersen @ 2007-10-22  7:23 UTC (permalink / raw)


Christos Chryssochoidis wrote:

> I would like to define a subtype of Wide_Character for a program
> that processes (unicode) text. This type would represent the Greek
> letters.

This sounds like what enumerated types are for.  You could do it like
this:

   type Faroese_Letter is ('a', 'A', 'b', 'B', 'd', 'D', '�', '�',
                           'e', 'E', [...],
                           'y', 'Y', '�', '�', '�', '�', '�', '�');
   -- optional representation clause

   function To_Wide_Wide_Character (Item : in Faroese_Letter)
     return Wide_Wide_Character;

   function To_Faroese_Letter (Item : in Wide_Wide_Character)
     return Faroese_Letter;

The conversion functions could make use of representation clauses,
"Image" and "Value" functions, or tables.

> Greek letters in Unicode, with all their diacritics, are
> located in two separate ranges: 0370 - 03D7 and 1F00 - 1FFF. That's
> 360 characters to write in an enumeration... Since gaps are not
> allowed in ranges, I 'm thinking instead of defining such a type, to
> define a function that would accept a Wide_Character as argument and
> return a boolean value indicating whether the given Wide_Character
> falls in the ranges of the Greek characters.

This could be done very simply using Ada.Strings.Maps.

How you should do it depends strongly on what you actually need your
Greek_Letter type for.

Greetings,

Jacob
-- 
"Only Hogwarts students really need spellcheckers"
                                -- An anonymous RISKS reader



^ permalink raw reply	[relevance 4%]

* Re: Copying string slices before calling subroutines?
  2007-05-04 22:27  7%                   ` Simon Wright
  2007-05-05  7:33  0%                     ` Jacob Sparre Andersen
@ 2007-05-05  7:41  0%                     ` Dmitry A. Kazakov
  1 sibling, 0 replies; 132+ results
From: Dmitry A. Kazakov @ 2007-05-05  7:41 UTC (permalink / raw)


On Fri, 04 May 2007 23:27:57 +0100, Simon Wright wrote:

> My reworking begins
> 
>    function Index
>      (Source  : String;
>       Pattern : String;
>       Going   : Ada.Strings.Direction := Ada.Strings.Forward;
>       Mapping : Ada.Strings.Maps.Character_Mapping
>         := Ada.Strings.Maps.Identity) return Natural
>    is
>       Cur_Index       : Natural;
>       Potential_Match : Boolean;
>       use Ada.Strings;
>       use Ada.Strings.Maps;
>    begin
>       if Pattern = "" then
>          raise Pattern_Error;
>       end if;
> 
>       --  Forwards case
> 
>       if Going = Forward then
>          for J in 1 .. Source'Length - Pattern'Length + 1 loop
>             Cur_Index := Source'First + J - 1;
>             Potential_Match := True;
>             for K in Pattern'Range loop
>                if Pattern (K) /=
>                  Value (Mapping, Source (Cur_Index + K - 1)) then
>                   Potential_Match := False;
>                   exit;
>                end if;
>             end loop;
>             if Potential_Match then
>                return Cur_Index;
>             end if;
>          end loop;
> 
> which calls Ada.Strings.Maps.Value rather more often than I suppose it
> could.

You can save remapping of Source, just there is no need to do it in advance
and allocate a full copy of Source. Instead of that, you make a ring buffer
of mod Pattern'Length where you store Value (Mapping, Source (i)). Once you
advance the main string index you "rotate" the buffer.

Then Pattern'Length = 1 should be a special case, as well as identity
mapping. Though, I don't know how efficient the latter could be.

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



^ permalink raw reply	[relevance 0%]

* Re: Copying string slices before calling subroutines?
  2007-05-04 22:27  7%                   ` Simon Wright
@ 2007-05-05  7:33  0%                     ` Jacob Sparre Andersen
  2007-05-05  7:41  0%                     ` Dmitry A. Kazakov
  1 sibling, 0 replies; 132+ results
From: Jacob Sparre Andersen @ 2007-05-05  7:33 UTC (permalink / raw)


Simon Wright <simon.j.wright@mac.com> writes:
> Jeffrey Creem <jeff@thecreems.com> writes:

>>  function Index
>>      (Source  : String;
>>       Pattern : String;
>>       Going   : Direction := Forward;
>>       Mapping : Maps.Character_Mapping := Maps.Identity) return Natural
>>    is
>>       Cur_Index     : Natural;
>>       Mapped_Source : String (Source'Range);
>
> There's the problem that I had (in my case Source'Length was >
> 2_000_000!) calling Index from one of my tasks.
>
> My reworking begins
[...]
> which calls Ada.Strings.Maps.Value rather more often than I suppose
> it could. But since the normal case is for the mapping to be the
> identity mapping the most useful optimisation would be to check for
> Identity and just compare directly.

Wouldn't the proper solution be to separate out Mapping =
Maps.Identity and Mapping /= Maps.Identity?  Even though we can do
cool things with default values for arguments, it isn't always
efficient.

   function Index
     (Source  : String;
      Pattern : String;
      Going   : Direction := Forward) return Natural;

   function Index
     (Source  : String;
      Pattern : String;
      Going   : Direction := Forward;
      Mapping : Maps.Character_Mapping) return Natural;

I can't see that there can be any cases, where existing code will work
differently with these two specifications instead of the existing
single specification.

We should also remember that for a compiler writer team, Mapping =
Maps.Identity may not be the normal case.

> Someone else was asking whether GNAT copies on the stack before the
> call -- I see no evidence of that.

Now that the implementation of Index has been pointed out to me, I
agree.  I could just see that it happened at some point during the
call to Index.

Greetings,

Jacob
-- 
�For there are only two reasons why war is made against a
 republic: The one, to become lord over her: the other, the
 fear of being occupied by her.�       -- Nicolo Machiavelli



^ permalink raw reply	[relevance 0%]

* Re: Copying string slices before calling subroutines?
  @ 2007-05-04 22:27  7%                   ` Simon Wright
  2007-05-05  7:33  0%                     ` Jacob Sparre Andersen
  2007-05-05  7:41  0%                     ` Dmitry A. Kazakov
  0 siblings, 2 replies; 132+ results
From: Simon Wright @ 2007-05-04 22:27 UTC (permalink / raw)


Jeffrey Creem <jeff@thecreems.com> writes:

>  function Index
>      (Source  : String;
>       Pattern : String;
>       Going   : Direction := Forward;
>       Mapping : Maps.Character_Mapping := Maps.Identity) return Natural
>    is
>       Cur_Index     : Natural;
>       Mapped_Source : String (Source'Range);

There's the problem that I had (in my case Source'Length was >
2_000_000!) calling Index from one of my tasks.

My reworking begins

   function Index
     (Source  : String;
      Pattern : String;
      Going   : Ada.Strings.Direction := Ada.Strings.Forward;
      Mapping : Ada.Strings.Maps.Character_Mapping
        := Ada.Strings.Maps.Identity) return Natural
   is
      Cur_Index       : Natural;
      Potential_Match : Boolean;
      use Ada.Strings;
      use Ada.Strings.Maps;
   begin
      if Pattern = "" then
         raise Pattern_Error;
      end if;

      --  Forwards case

      if Going = Forward then
         for J in 1 .. Source'Length - Pattern'Length + 1 loop
            Cur_Index := Source'First + J - 1;
            Potential_Match := True;
            for K in Pattern'Range loop
               if Pattern (K) /=
                 Value (Mapping, Source (Cur_Index + K - 1)) then
                  Potential_Match := False;
                  exit;
               end if;
            end loop;
            if Potential_Match then
               return Cur_Index;
            end if;
         end loop;

which calls Ada.Strings.Maps.Value rather more often than I suppose it
could. But since the normal case is for the mapping to be the identity
mapping the most useful optimisation would be to check for Identity
and just compare directly.


Someone else was asking whether GNAT copies on the stack before the
call -- I see no evidence of that. I had to provide my own
implementation of this Ada05 routine because my code has to be Ada95,
and it shows no sign of excessive stack use:

   function Index
     (Source : String;
      Pattern : String;
      From : Positive;
      Going : Ada.Strings.Direction := Ada.Strings.Forward;
      Mapping : Ada.Strings.Maps.Character_Mapping
        := Ada.Strings.Maps.Identity)
     return Natural is
      Candidate : String renames Source (From .. Source'Last);
   begin
      return Index (Source => Candidate,
                    Pattern => Pattern,
                    Going => Going,
                    Mapping => Mapping);
   end Index;



^ permalink raw reply	[relevance 7%]

* Re: STORAGE_ERROR : EXCEPTION_STACK_OVERFLOW
  @ 2007-04-02 14:11  3%   ` andrew.carroll
  0 siblings, 0 replies; 132+ results
From: andrew.carroll @ 2007-04-02 14:11 UTC (permalink / raw)


All the files are below.  The last file in the list, called
tables.txt, is the input file.  I've supplied the input file I am
using when I get the errors.





with Ada.Text_IO, Ada.Directories, GNAT.Calendar.Time_IO,
Ada.Characters.Latin_1, Ada.IO_Exceptions,
 Ada.Strings.Maps.Constants, Ada.Strings.Fixed,
Ada.Characters.Handling, Ada.Calendar,
 schema_types, attribute_types, parser, util, index_types;

use parser, GNAT.Calendar.Time_IO, Ada.Characters.Latin_1,
Ada.Strings.Maps.Constants, Ada.Strings.Fixed,
Ada.Characters.Handling, Ada.Calendar, schema_types, attribute_types,
util;

procedure dbprog is

    -- the input file contains the table specifications --
    input : Ada.Text_IO.File_Type;

    ------------------------------------
    --    Variables for Processing    --
    ------------------------------------
    char      : Character;
    line      : string_ptr;
    tablename : string_ptr;
    datacols  : string_array_ptr;
    pkcols    : string_array_ptr;
    schemas   : schema_array_ptr;
    sindex    : Integer := 1;
    tupls     : tuple_ptr;

    procedure showoptionsmenu is
    begin
        cls;
        pl ("---------------------------------------------------",
True);
        pl ("Type one of the following at the prompt:", True);
        pl (" ", True);
        pl ("~  QUIT ", True);
        pl ("1  INSERT DATA", True);
        pl ("2  UPDATE DATA", True);
        pl ("3  DELETE DATA", True);
        pl ("4  SHOW RECORDS", True);
        pl ("For help type 'help'", True);
        pl ("---------------------------------------------------",
True);
        pl (">>", False);

        while Ada.Text_IO.End_Of_Line loop
            Ada.Text_IO.Skip_Line;
        end loop;

        line := new String'(Ada.Text_IO.Get_Line);

    end showoptionsmenu;

    function markschema return Integer is
        idx : Integer := 0;
    begin
        --find the schema in schemas.
        if schemas'length <= 0 then
            return idx;
        end if;

        loop
            idx := idx + 1;
            exit when idx > schemas'length
                     or else Index (To_Upper (schemas
(idx).tablename), tablename.all) > 0;
        end loop;

        return idx;

    end markschema;

    procedure getcolumnnamesandvalues is
        year  : Year_Number;
        month : Month_Number;
        day   : Day_Number;
        line  : string_ptr := new String'("");
        valid : Boolean    := False;
    begin
        --markschema sets sindex to the appropriate index in schemas
        --for the table with tablename.
        sindex := markschema;

        --tables are already loaded and ready to go.
        datacols := new string_array (1 .. schemas
(sindex).attributes'length);

        for x in  1 .. schemas (sindex).attributes'length loop
            if Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) = "DATE" then

                while not valid loop
                    pl
                       ("Enter a YEAR (1901 - 2099) for " &
                        Trim (schemas (sindex).attributes (x).name,
Ada.Strings.Both) &
                        "  >>",
                        False,
                        False);

                    while Ada.Text_IO.End_Of_Line loop
                        Ada.Text_IO.Skip_Line;
                    end loop;

                    line := new String'(Ada.Text_IO.Get_Line);

                    if Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) > 0 then
                        pl ("!! INVALID !!", True, False);
                    elsif Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) <= 0
                       and then Integer'value (line.all) not  in
Ada.Calendar.Year_Number'range
                    then
                        pl ("!! INVALID !!", True, False);
                    else
                        valid := True;
                    end if;
                end loop;

                year  := Year_Number'value (line.all);
                valid := False;

                while not valid loop
                    pl
                       ("Enter a MONTH NUMBER for " &
                        Trim (schemas (sindex).attributes (x).name,
Ada.Strings.Both) &
                        "  >>",
                        False,
                        False);

                    while Ada.Text_IO.End_Of_Line loop
                        Ada.Text_IO.Skip_Line;
                    end loop;

                    line := new String'(Ada.Text_IO.Get_Line);

                    if Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) > 0 then
                        pl ("!! INVALID !!", True, False);
                    elsif Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) <= 0
                       and then Integer'value (line.all) not  in
Ada.Calendar.Month_Number'range
                    then
                        pl ("!! INVALID !!", True, False);
                    else
                        valid := True;
                    end if;
                end loop;

                month := Month_Number'value (line.all);
                valid := False;

                while not valid loop
                    pl
                       ("Enter a DAY NUMBER for " &
                        Trim (schemas (sindex).attributes (x).name,
Ada.Strings.Both) &
                        "  >>",
                        False,
                        False);

                    while Ada.Text_IO.End_Of_Line loop
                        Ada.Text_IO.Skip_Line;
                    end loop;

                    line := new String'(Ada.Text_IO.Get_Line);

                    if Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) > 0 then
                        pl ("!! INVALID !!", True, False);
                    elsif Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) <= 0
                       and then Integer'value (line.all) not  in
Ada.Calendar.Day_Number'range
                    then
                        pl ("!! INVALID !!", True, False);
                    else
                        valid := True;
                    end if;
                end loop;

                day              := Day_Number'value (line.all);
                datacols.all (x) := new String'(Image (Time_Of (year,
month, day), ISO_Date));
                valid            := False;
            else
                while not valid loop
                    pl
                       ("Enter a value for " &
                        Trim (schemas (sindex).attributes (x).name,
Ada.Strings.Both) &
                        "(" &
                        Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) &
                        ")  >>",
                        False,
                        False);

                    while Ada.Text_IO.End_Of_Line loop
                        Ada.Text_IO.Skip_Line;
                    end loop;

                    line := new String'(Ada.Text_IO.Get_Line);

                    if Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                       "BOOLEAN"
                    then
                        if To_Upper (line.all) = "TRUE" then
                            line  := new String'("True");
                            valid := True;
                        elsif To_Upper (line.all) = "FALSE" then
                            line  := new String'("False");
                            valid := True;
                        elsif line.all = "1" then
                            line  := new String'("True");
                            valid := True;
                        elsif line.all = "0" then
                            line  := new String'("False");
                            valid := True;
                        else
                            pl ("!! INVALID !!", True, False);
                        end if;
                    elsif Trim (schemas (sindex).attributes
(x).domain, Ada.Strings.Both) =
                          "INTEGER"
                    then
                        if Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) <= 0 then
                            valid := True;
                        else
                            pl ("!! INVALID !!", True, False);
                        end if;
                    else --"STRING"
                        valid := True;
                    end if;

                end loop;

                valid            := False;
                datacols.all (x) := new String'(line.all);
            end if;

        end loop;

    end getcolumnnamesandvalues;

    procedure getprimarykeynamesandvalues is
        year  : Year_Number;
        month : Month_Number;
        day   : Day_Number;
        line  : string_ptr := new String'("");
        valid : Boolean    := False;
    begin
        --markschema sets sindex to the appropriate index in schemas
        --for the table with tablename.
        sindex := markschema;

        pl ("Provide the primary key values to identify the record to
delete.", False, True);
        pl ("Press Enter to continue...", True, True);
        Ada.Text_IO.Get_Immediate (char);

        --tables are already loaded and ready to go.
        pkcols := new string_array (1 .. schemas
(sindex).primary_key_count);

        for x in  1 .. schemas (sindex).attributes'length loop
            if schemas (sindex).attributes (x).isprimarykey then
                if Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) = "DATE" then

                    while not valid loop
                        pl
                           ("Enter a YEAR (1901 - 2099) for " &
                            Trim (schemas (sindex).attributes
(x).name, Ada.Strings.Both) &
                            "  >>",
                            False,
                            False);

                        while Ada.Text_IO.End_Of_Line loop
                            Ada.Text_IO.Skip_Line;
                        end loop;

                        line := new String'(Ada.Text_IO.Get_Line);

                        if Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) > 0 then
                            pl ("!! INVALID !!", True, False);
                        elsif Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) <= 0
                           and then Integer'value (line.all) not  in
Ada.Calendar.Year_Number'range
                        then
                            pl ("!! INVALID !!", True, False);
                        else
                            valid := True;
                        end if;
                    end loop;

                    year  := Year_Number'value (line.all);
                    valid := False;

                    while not valid loop
                        pl
                           ("Enter a MONTH NUMBER for " &
                            Trim (schemas (sindex).attributes
(x).name, Ada.Strings.Both) &
                            "  >>",
                            False,
                            False);

                        while Ada.Text_IO.End_Of_Line loop
                            Ada.Text_IO.Skip_Line;
                        end loop;

                        line := new String'(Ada.Text_IO.Get_Line);

                        if Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) > 0 then
                            pl ("!! INVALID !!", True, False);
                        elsif Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) <= 0
                           and then Integer'value (line.all) not  in
Ada.Calendar.Month_Number'
                             range
                        then
                            pl ("!! INVALID !!", True, False);
                        else
                            valid := True;
                        end if;
                    end loop;

                    month := Month_Number'value (line.all);
                    valid := False;

                    while not valid loop
                        pl
                           ("Enter a DAY NUMBER for " &
                            Trim (schemas (sindex).attributes
(x).name, Ada.Strings.Both) &
                            "  >>",
                            False,
                            False);

                        while Ada.Text_IO.End_Of_Line loop
                            Ada.Text_IO.Skip_Line;
                        end loop;

                        line := new String'(Ada.Text_IO.Get_Line);

                        if Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) > 0 then
                            pl ("!! INVALID !!", True, False);
                        elsif Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) <= 0
                           and then Integer'value (line.all) not  in
Ada.Calendar.Day_Number'range
                        then
                            pl ("!! INVALID !!", True, False);
                        else
                            valid := True;
                        end if;
                    end loop;

                    day            := Day_Number'value (line.all);
                    pkcols.all (x) := new String'(Image (Time_Of
(year, month, day), ISO_Date));
                    valid          := False;
                else
                    while not valid loop
                        pl
                           ("Enter a value for " &
                            Trim (schemas (sindex).attributes
(x).name, Ada.Strings.Both) &
                            "(" &
                            Trim (schemas (sindex).attributes
(x).domain, Ada.Strings.Both) &
                            ")  >>",
                            False,
                            False);

                        while Ada.Text_IO.End_Of_Line loop
                            Ada.Text_IO.Skip_Line;
                        end loop;

                        line := new String'(Ada.Text_IO.Get_Line);

                        if Trim (schemas (sindex).attributes
(x).domain, Ada.Strings.Both) =
                           "BOOLEAN"
                        then
                            if To_Upper (line.all) = "TRUE" then
                                line  := new String'("True");
                                valid := True;
                            elsif To_Upper (line.all) = "FALSE" then
                                line  := new String'("False");
                                valid := True;
                            elsif line.all = "1" then
                                line  := new String'("True");
                                valid := True;
                            elsif line.all = "0" then
                                line  := new String'("False");
                                valid := True;
                            else
                                pl ("!! INVALID !!", True, False);
                            end if;
                        elsif Trim (schemas (sindex).attributes
(x).domain, Ada.Strings.Both) =
                              "INTEGER"
                        then
                            if Index (line.all, Decimal_Digit_Set,
Ada.Strings.Outside) <=
                               0
                            then
                                valid := True;
                            else
                                pl ("!! INVALID !!", True, False);
                            end if;
                        else --"STRING"
                            valid := True;
                        end if;

                    end loop;

                    valid          := False;
                    pkcols.all (x) := new String'(line.all);
                end if;
            end if;

        end loop;
    end getprimarykeynamesandvalues;

    procedure gettablename is
        count : Integer := 1;
    begin
        pl ("Enter the table name in CAPITAL letters >>", False);
        tablename     := new String'(Ada.Text_IO.Get_Line);
        tablename.all := To_Upper (tablename.all);

        while not Ada.Directories.Exists (tablename.all) and count < 5
loop
            pl ("Enter the table name in CAPITAL letters >>", False);
            tablename     := new String'(Ada.Text_IO.Get_Line);
            tablename.all := To_Upper (tablename.all);
            count         := count + 1;
        end loop;

        if count >= 5 then
            raise Constraint_Error;
        end if;

    end gettablename;

    procedure getchosenoptiondata is
    begin
        gettablename;

        --we don't do "4" here because it is just a select and we
don't
        --need values for it and we already have the attribute names
in
        --the schemas(sindex) object for which to SELECT or SHOW the
        --data.
        if line.all = "1" then
            getcolumnnamesandvalues;
        elsif line.all = "2" then
            getprimarykeynamesandvalues;
            pl (" ", True, True);
            pl ("Please enter new values for each item.  You can enter
the same ", True, True);
            pl ("data if you don't want it modified.", True, True);
            pl (" ", True, True);
            getcolumnnamesandvalues;
        elsif line.all = "3" then
            getprimarykeynamesandvalues;

        end if;

    end getchosenoptiondata;

    procedure parsechosenoption is
        pkattribs  : attribute_array_ptr;
        newvalues  : attribute_array_ptr;
        linelength : Integer;
        outline    : string_ptr;
    begin
        if line.all = "1" then

            -------------------
            --  INSERT DATA  --
            -------------------
            newvalues := new attribute_array (1 .. schemas
(sindex).attributes'length);

            --fill in the values on the objects and pass that to
insert.
            for x in  1 .. newvalues'length loop
                if Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                   "BOOLEAN"
                then
                    newvalues (x) :=
                     new booleanattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => Boolean'value (datacols
(x).all));
                elsif Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                      "STRING"
                then
                    newvalues (x) :=
                     new stringattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => max_stringlength * ' ');

                    Replace_Slice
                       (stringattribute (newvalues (x).all).value,
                        1,
                        max_stringlength,
                        datacols (x).all);

                elsif Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                      "INTEGER"
                then
                    newvalues (x) :=
                     new integerattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => Integer'value (datacols
(x).all));

                else -- "DATE"
                    newvalues (x) :=
                     new dateattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => Value (datacols (x).all),
                        year         => Year (Value (datacols
(x).all)),
                        month        => Month (Value (datacols
(x).all)),
                        day          => Day (Value (datacols
(x).all)));
                end if;
            end loop;

            insertrec (schemas (sindex).all, newvalues.all);

        elsif line.all = "2" then

            -------------------
            --  UPDATE DATA  --
            -------------------
            pkattribs := new attribute_array (1 .. pkcols'length);

            --fill in the values on the objects and pass that to
insert.
            for x in  1 .. pkcols'length loop
                if Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                   "BOOLEAN"
                then
                    pkattribs (x) :=
                     new booleanattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => Boolean'value (pkcols
(x).all));
                elsif Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                      "STRING"
                then

                    pkattribs (x) :=
                     new stringattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => max_stringlength * ' ');

                    Replace_Slice
                       (stringattribute (pkattribs (x).all).value,
                        1,
                        max_stringlength,
                        pkcols (x).all);

                elsif Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                      "INTEGER"
                then
                    pkattribs (x) :=
                     new integerattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => Integer'value (pkcols
(x).all));

                else -- "DATE"
                    pkattribs (x) :=
                     new dateattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => Value (pkcols (x).all),
                        year         => Year (Value (pkcols (x).all)),
                        month        => Month (Value (pkcols
(x).all)),
                        day          => Day (Value (pkcols (x).all)));
                end if;
            end loop;

            newvalues := new attribute_array (1 .. schemas
(sindex).attributes'length);

            --fill in the values on the objects and pass that to
insert.
            for x in  1 .. newvalues'length loop
                if Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                   "BOOLEAN"
                then
                    newvalues (x) :=
                     new booleanattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => Boolean'value (datacols
(x).all));
                elsif Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                      "STRING"
                then
                    newvalues (x) :=
                     new stringattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => max_stringlength * ' ');

                    Replace_Slice
                       (stringattribute (newvalues (x).all).value,
                        1,
                        max_stringlength,
                        datacols (x).all);

                elsif Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                      "INTEGER"
                then
                    newvalues (x) :=
                     new integerattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => Integer'value (datacols
(x).all));

                else -- "DATE"
                    newvalues (x) :=
                     new dateattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => Value (datacols (x).all),
                        year         => Year (Value (datacols
(x).all)),
                        month        => Month (Value (datacols
(x).all)),
                        day          => Day (Value (datacols
(x).all)));
                end if;
            end loop;

            updaterec (schemas (sindex).all, pkattribs.all,
newvalues.all);

        elsif line.all = "3" then

            -------------------
            --  DELETE DATA  --
            -------------------
            Ada.Text_IO.Put_Line (Integer'image (sindex));
            Ada.Text_IO.Put_Line (tablename.all);

            pkattribs := new attribute_array (1 .. pkcols'length);

            --fill in the values on the objects and pass that to
delete.
            for x in  1 .. pkcols'length loop
                if Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                   "BOOLEAN"
                then
                    pkattribs (x) :=
                     new booleanattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => Boolean'value (pkcols
(x).all));
                elsif Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                      "STRING"
                then

                    pkattribs (x) :=
                     new stringattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => max_stringlength * ' ');

                    Replace_Slice
                       (stringattribute (pkattribs (x).all).value,
                        1,
                        max_stringlength,
                        pkcols (x).all);

                elsif Trim (schemas (sindex).attributes (x).domain,
Ada.Strings.Both) =
                      "INTEGER"
                then
                    pkattribs (x) :=
                     new integerattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => Integer'value (pkcols
(x).all));

                else -- "DATE"
                    pkattribs (x) :=
                     new dateattribute'
                       (name         => schemas (sindex).attributes
(x).name,
                        domain       => schemas (sindex).attributes
(x).domain,
                        isprimarykey => schemas (sindex).attributes
(x).isprimarykey,
                        byte_start   => 0,
                        byte_end     => 0,
                        value        => Value (pkcols (x).all),
                        year         => Year (Value (pkcols (x).all)),
                        month        => Month (Value (pkcols
(x).all)),
                        day          => Day (Value (pkcols (x).all)));
                end if;
            end loop;

            deleterec (schemas (sindex).all, pkattribs.all);

        elsif line.all = "4" then

            ----------------------
            --  SELECT RECORDS  --
            ----------------------
            linelength := 60;
            sindex     := markschema;
            outline    := new String'(1 .. linelength => '-');
            pl (outline.all, True, False);
            pl (schemas (sindex).tablename, True, False);
            pl (outline.all, True, False);
            pl ("| ", False, False);
            for x in  1 .. schemas (sindex).attributes'length loop
                pl (Trim (schemas (sindex).attributes (x).name,
Ada.Strings.Both), False, False);

                if x < schemas (sindex).attributes'length then
                    pl (" | ", False, False);
                end if;

            end loop;
            pl (" |", True, False);
            pl (outline.all, True, False);

            tupls := selectrec (schemas (sindex).all);

            if tupls = null then
                pl ("No Data", True, False);
            else
                for y in  1 .. tupls'length loop
                    newvalues := tupls (y);

                    for x in  1 .. newvalues'length loop
                        if Trim (newvalues (x).domain,
Ada.Strings.Both) = "BOOLEAN" then
                            pl
                               (Trim
                                    (Boolean'image (booleanattribute
(newvalues (x).all).value),
                                     Ada.Strings.Both),
                                False,
                                False);
                        elsif Trim (newvalues (x).domain,
Ada.Strings.Both) = "STRING" then
                            pl
                               (Trim
                                    (stringattribute (newvalues
(x).all).value,
                                     Ada.Strings.Both),
                                False,
                                False);
                        elsif Trim (newvalues (x).domain,
Ada.Strings.Both) = "INTEGER" then
                            pl
                               (Trim
                                    (Integer'image (integerattribute
(newvalues (x).all).value),
                                     Ada.Strings.Both),
                                False,
                                False);
                        else -- "DATE"
                            pl
                               (Trim
                                    (Image (dateattribute (newvalues
(x).all).value, ISO_Date),
                                     Ada.Strings.Both),
                                False,
                                False);
                        end if;

                        if x < newvalues'length then
                            pl ("   ", False, False);
                        end if;

                    end loop;
                    pl (" ", True, False);
                end loop;
            end if;

            pl (outline.all, True, False);
            pl ("Press Enter  >>", False, False);
            Ada.Text_IO.Get_Immediate (char);
        end if;

        sindex    := 0;
        tablename := null;
        datacols  := null;
        pkcols    := null;
        tupls     := null;

    end parsechosenoption;

begin

    cls;
    pl ("---------------------------------------------------", True);
    pl ("Put your table definitions in a file named ", True);
    pl ("tables.txt and place the file in the same folder as", True);
    pl ("this program (Parser.exe).  Type C to continue or.", True);
    pl ("~ to quit.", True);
    pl ("---------------------------------------------------", True);
    pl (">>", False);
    Ada.Text_IO.Get (char);
    line := new String'(Ada.Text_IO.Get_Line);

    if char = ETX or char = Tilde then
        raise Ada.IO_Exceptions.End_Error;
    end if;

    setinputfile ("tables.txt");
    schemas := parsetables;
    closeinputfile;
    showoptionsmenu;

    while line.all /= "~" loop

        if line.all = "help" or line.all = "HELP" then
            pl ("---------------------------------------------------",
True);
            pl ("If you want to quit type the tilde '~' character",
True);
            pl ("---------------------------------------------------",
True);
            pl (">>", False);
            line := new String'(Ada.Text_IO.Get_Line);
            cls;
        elsif line.all = "goodbye" or
              line.all = "GOODBYE" or
              line.all = "exit" or
              line.all = "EXIT" or
              line.all = "quit" or
              line.all = "QUIT" or
              line.all = "q" or
              line.all = "Q"
        then
            line := new String'("~");
        else
            ------------------------
            --   output results   --
            ------------------------
            getchosenoptiondata;
            parsechosenoption;
            showoptionsmenu;

        end if;

    end loop;

    cls;
    pl ("---------------------------------------------------", True);
    pl ("Goodbye!", True);
    pl ("---------------------------------------------------", True);

exception
    when Ada.IO_Exceptions.End_Error =>
        if Ada.Text_IO.Is_Open (input) then
            Ada.Text_IO.Close (input);
        end if;
        cls;
        pl ("---------------------------------------------------",
True);
        pl ("An error occured while reading data.  Possibly a
missing", True);
        pl ("semi-colon or other format character.  Or, you pressed ",
True);
        pl ("CTRL + C.  Goodbye!", True);
        pl ("---------------------------------------------------",
True);

    when Ada.Calendar.Time_Error =>
        pl ("A date value was not entered correctly.", True);
        pl ("Unfortunately this will cause the program to exit.",
True);
        pl ("Your data is safe so long as you don't 'create fresh'.",
True);
        pl ("the table when you start the program again.", True);
    when Ada.IO_Exceptions.Data_Error =>
        if Ada.Text_IO.Is_Open (input) then
            Ada.Text_IO.Close (input);
        end if;
    when Constraint_Error =>
        Ada.Text_IO.Put_Line ("You entered the data wrong.");

end dbprog;


with Ada.Text_IO, schema_types, attribute_types;

use schema_types, attribute_types;

package parser is

    file : Ada.Text_IO.File_Type;

    ---------------------------
    --    Utility Methods    --
    ---------------------------
    procedure setinputfile (filename : String);
    procedure closeinputfile;
    function parsetables return schema_array_ptr;
    function parsetable return schema'class;
    function parseattributes return attribute_array_ptr;
    function parseattribute return attribute'class;

end parser;


with Ada.Text_IO, Ada.Directories, Ada.Integer_Text_IO,
Ada.Strings.Fixed, Ada.Characters.Latin_1,
 Ada.IO_Exceptions, schema_types, attribute_types, util;

use Ada.Strings.Fixed, Ada.Characters.Latin_1, schema_types,
attribute_types, util;

package body parser is

    procedure setinputfile (filename : String) is

    begin
        Ada.Text_IO.Open (file, Ada.Text_IO.In_File, filename);
    end setinputfile;

    procedure closeinputfile is
    begin
        if Ada.Text_IO.Is_Open (file) then
            Ada.Text_IO.Close (file);
        end if;
    end closeinputfile;

    -----------------------
    --    parseTables    --
    -----------------------
    function parsetables return schema_array_ptr is
        eof        : Boolean          := False;
        char       : Character;
        schemas    : schema_array_ptr := null;
        swap       : schema_array_ptr := null;
        schemainfo : schema_ptr       := null;
        i          : Integer          := 1;
    begin
        eatWhite (file, eof);

        if not eof then
            Ada.Text_IO.Look_Ahead (file, char, eof);
        else
            raise Ada.IO_Exceptions.End_Error;
        end if;

        --at this point we should be ready to read the table name.
        swap := new schema_array (1 .. max_tables);

        while not eof loop

            schemainfo := new schema'class'(parsetable);

            pl ("Create the table fresh? [y/Y] >>", False, True);
            Ada.Text_IO.Get (char);

	    swap(i) := new schema(schemainfo.attributes'length);

            if char = 'y' or char = 'Y' then
                swap (i)     := schemainfo;
                createtable (swap (i));
            else
                if Ada.Directories.Exists (schemainfo.tablename) then
                    swap (i) := loadtable (schemainfo.tablename);
                else
                    pl ("No table exists on disc with name = " &
schemainfo.tablename, True, True);
                    pl ("You will not be able to query " &
schemainfo.tablename, True, True);
                    pl (" ", True, False);
                end if;
            end if;

	    i := i + 1;
            eatWhite (file, eof);

            if not eof then
                Ada.Text_IO.Look_Ahead (file, char, eof);
            end if;
        end loop;

        i := i - 1;

        if i < 1 then
            schemas := null;
            swap    := null;
        else
            schemas := new schema_array (1 .. i);

            for x in  1 .. i loop
                schemas (x) := swap (x);
            end loop;

            swap := null;

        end if;

        return schemas;

    end parsetables;

    ----------------------
    --    parseTable    --
    ----------------------
    function parsetable return schema'class is
        temp    : schema_ptr := null;
        eof     : Boolean    := False;
        char    : Character;
        tname   : String (1 .. max_tablename_length);
        attribs : attribute_array_ptr;
        i       : Integer    := 1;
    begin

        eatWhite (file, eof);

        --at this point we should be ready to read the table name.
        --the call to eatwhite might be redundant from the instance
that
        --called 'me' but we want to ensure we are in the right
location within
        --the file.
        if not eof then
            Ada.Text_IO.Look_Ahead (file, char, eof);
        else
            raise Ada.IO_Exceptions.End_Error;
        end if;

        while char /= Space and
              char /= HT and
              char /= LF and
              char /= CR and
              char /= Left_Parenthesis and
              not eof
        loop

            Ada.Text_IO.Get (file, char);
            tname (i) := char;
            i         := i + 1;
            Ada.Text_IO.Look_Ahead (file, char, eof);
        end loop;

        for x in  i .. max_tablename_length loop
            tname (x) := ' ';
        end loop;

        --We just read the table name.  We are expecting an opening
'('.
        --If it's not there then there is a problem with the input
file
        --format.
        eatWhite (file, eof);

        if not eof then
            Ada.Text_IO.Look_Ahead (file, char, eof);

            if char = Left_Parenthesis then
                Ada.Text_IO.Get (file, char);
            else
                Ada.Text_IO.Put_Line(
"        Error in input file format:  No attributes found.  Must have
(<attribute list>)");
            end if;
        else
            raise Ada.IO_Exceptions.End_Error;
        end if;

        attribs := parseattributes;

        if attribs /= null then

            temp            := new schema (attribs.all'length);
            temp.attributes := attribs.all;
            temp.tablename  := tname;

            for x in  1 .. temp.attributes'length loop
                if temp.attributes (x).all.isprimarykey then
                    temp.primary_key_count := temp.primary_key_count +
1;
                end if;
            end loop;
        else
            temp := null;
        end if;

        --at this point we should have read the ')' for the whole
table spec.
        --if we peek, we should find a ';'.
        eatWhite (file, eof);

        if not eof then
            Ada.Text_IO.Look_Ahead (file, char, eof);

            if char = Semicolon then
                Ada.Text_IO.Get (file, char);
            else
                Ada.Text_IO.Put_Line
                   ("        Error in input file format:  Missing
closing ';' on table spec.");
                temp := null;
            end if;
        else
            Ada.Text_IO.Put_Line
               ("        Error in input file format:  Missing closing
')' on table spec.");
            temp := null;
        end if;

        return temp.all;

    end parsetable;

    ---------------------------
    --    parseAttributes    --
    ---------------------------
    function parseattributes return attribute_array_ptr is
        eof     : Boolean             := False;
        char    : Character;
        attribs : attribute_array_ptr := null;
        swap    : attribute_array_ptr := null;
        i       : Integer             := 1;
    begin
        eatWhite (file, eof);

        if not eof then
            Ada.Text_IO.Look_Ahead (file, char, eof);
        else
            raise Ada.IO_Exceptions.End_Error;
        end if;

        --at this point we should be ready to read the attribute name.
        if not eof and char /= Right_Parenthesis then
            Ada.Text_IO.Look_Ahead (file, char, eof);
        else
            Ada.Text_IO.Put_Line ("            found eof prematurely
or ')' is in wrong place.");
            raise Ada.IO_Exceptions.End_Error;
        end if;

        swap := new attribute_array (1 .. max_columns);

        while char /= Right_Parenthesis and char /= Semicolon and not
eof loop
            swap (i) := new attribute'class'(parseattribute);
            i        := i + 1;
            eatWhite (file, eof);

            if not eof and char /= Right_Parenthesis then
                --we are expecting a ')' or a comma.
                Ada.Text_IO.Look_Ahead (file, char, eof);
            else
                raise Ada.IO_Exceptions.End_Error;
            end if;

            if char /= Comma and char /= Right_Parenthesis and not eof
then
                Ada.Text_IO.Put_Line
                   ("            Error in input file:  Missing comma
between attributes.");
                eof  := True;
                swap := null;
            elsif not eof then
                --read the comma or the ')'
                Ada.Text_IO.Get (file, char);
            end if;

            eatWhite (file, eof);

            if eof then
                Ada.Text_IO.Put_Line ("Missing semi-colon or other
format error.");
                raise Ada.IO_Exceptions.End_Error;
            end if;

        end loop;

        i := i - 1;

        if i < 1 then
            swap := null;
        else
            attribs := new attribute_array (1 .. i);

            for x in  1 .. i loop
                attribs (x) := swap (x);
            end loop;

            swap := null;

        end if;

        return attribs;

    end parseattributes;

    --------------------------
    --    parseAttribute    --
    --------------------------
    function parseattribute return attribute'class is
        temp         : attribute_types.attribute_ptr;
        eof          : Boolean := False;
        char         : Character;
        aname        : String (1 .. max_attributename_length);
        atype        : String (1 .. max_typename_length);
        asize        : Integer;
        isprimarykey : Boolean := False;
        i            : Integer := 1;
    begin

        if not eof then
            Ada.Text_IO.Look_Ahead (file, char, eof);
        else
            raise Ada.IO_Exceptions.End_Error;
        end if;

        while char /= Space and
              char /= HT and
              char /= LF and
              char /= CR and
              char /= Left_Parenthesis and
              char /= Colon and
              not eof
        loop
            Ada.Text_IO.Get (file, char);
            aname (i) := char;
            i         := i + 1;
            Ada.Text_IO.Look_Ahead (file, char, eof);
        end loop;

        for x in  i .. max_attributename_length loop
            aname (x) := ' ';
        end loop;

        --at this point we have the attribute name.  Read white space
to
        --a parenthesis or an colon.
        eatWhite (file, eof);

        if not eof then
            Ada.Text_IO.Look_Ahead (file, char, eof);
        else
            raise Ada.IO_Exceptions.End_Error;
        end if;

        --the next character should be '(' or ':'
        if char = Left_Parenthesis then
            Ada.Text_IO.Get (file, char);
            eatWhite (file, eof);

            i := 1;

            --read "primary"
            while char /= Space and
                  char /= HT and
                  char /= LF and
                  char /= CR and
                  char /= Right_Parenthesis and
                  not eof
            loop
                Ada.Text_IO.Get (file, char);
                atype (i) := char;
                i         := i + 1;
                Ada.Text_IO.Look_Ahead (file, char, eof);
            end loop;

            for x in  i .. max_typename_length loop
                atype (x) := ' ';
            end loop;

            if Trim (atype, Ada.Strings.Both) = "PRIMARY" then
                isprimarykey := True;
            end if;

            eatWhite (file, eof);

            if not eof then
                Ada.Text_IO.Look_Ahead (file, char, eof);
            else
                raise Ada.IO_Exceptions.End_Error;
            end if;

            i := 1;

            --read "key"
            while char /= Space and
                  char /= HT and
                  char /= LF and
                  char /= CR and
                  char /= Right_Parenthesis and
                  not eof
            loop
                Ada.Text_IO.Get (file, char);
                atype (i) := char;
                i         := i + 1;
                Ada.Text_IO.Look_Ahead (file, char, eof);
            end loop;

            for x in  i .. max_typename_length loop
                atype (x) := ' ';
            end loop;

            if Trim (atype, Ada.Strings.Both) = "KEY" then
                isprimarykey := True;
            else
                isprimarykey := False;
            end if;

            eatWhite (file, eof);

            if not eof then
                Ada.Text_IO.Look_Ahead (file, char, eof);
            else
                raise Ada.IO_Exceptions.End_Error;
            end if;

            if char = ')' then
                Ada.Text_IO.Get (file, char);
            else
                Ada.Text_IO.Put_Line
                   ("            Error in input:  Missing ')' after
Primary Key designation.");
            end if;

            eatWhite (file, eof);

            if not eof then
                Ada.Text_IO.Look_Ahead (file, char, eof);
            else
                raise Ada.IO_Exceptions.End_Error;
            end if;

        end if;

        if char = Colon then
            Ada.Text_IO.Get (file, char);

            eatWhite (file, eof);

            if not eof then
                Ada.Text_IO.Look_Ahead (file, char, eof);
            else
                raise Ada.IO_Exceptions.End_Error;
            end if;

            i := 1;

            --read the type of the attribute into atype variable
            while char /= Space and
                  char /= HT and
                  char /= LF and
                  char /= CR and
                  char /= Comma and
                  char /= Left_Parenthesis and
                  char /= Right_Parenthesis and
                  char /= Semicolon and
                  not eof
            loop
                Ada.Text_IO.Get (file, char);
                atype (i) := char;
                i         := i + 1;
                Ada.Text_IO.Look_Ahead (file, char, eof);
            end loop;

            for x in  i .. max_typename_length loop
                atype (x) := ' ';
            end loop;

            eatWhite (file, eof);

            --read the left parenthesis
            if not eof and
               char = Left_Parenthesis and
               Trim (atype, Ada.Strings.Both) = "STRING"
            then
                Ada.Text_IO.Get (file, char);
                Ada.Text_IO.Look_Ahead (file, char, eof);
            elsif not eof and
                  char /= Left_Parenthesis and
                  Trim (atype, Ada.Strings.Both) = "STRING"
            then
                Ada.Text_IO.Put_Line ("            Incorrect syntax:
missing (size) for string.");
            elsif eof then
                raise Ada.IO_Exceptions.End_Error;
            end if;

            eatWhite (file, eof);

            if not eof then
                Ada.Text_IO.Look_Ahead (file, char, eof);
            else
                raise Ada.IO_Exceptions.End_Error;
            end if;

            --read the size of the type of the attribute into atype
variable
            while char /= Space and
                  char /= HT and
                  char /= LF and
                  char /= CR and
                  char /= Comma and
                  char /= Right_Parenthesis and
                  char /= Left_Parenthesis and
                  not eof
            loop

                Ada.Integer_Text_IO.Get (file, asize, 0);
                Ada.Text_IO.Look_Ahead (file, char, eof);
            end loop;

            --I have to do this temporarily to get this program
            --to work.  ALL strings are the same length.  The reason
            --is because there is no way to know how long the string
is
            --when serializing it in from a file (see loadtable in
            --schema_types) before we serialize it so that we can
            --provide a length discriminant to the type defined in
            --attribute_types.  So, we just make them all the same
            --length.
            asize := max_stringlength;

            eatWhite (file, eof);

            --read the right parenthesis
            if not eof and
               char = Right_Parenthesis and
               Trim (atype, Ada.Strings.Both) = "STRING"
            then
                Ada.Text_IO.Get (file, char);
                Ada.Text_IO.Look_Ahead (file, char, eof);
            elsif not eof and
                  char /= Right_Parenthesis and
                  Trim (atype, Ada.Strings.Both) = "STRING"
            then
                Ada.Text_IO.Put_Line
                   ("            Incorrect syntax:  missing (size ~)~
for string.");
            elsif eof then
                raise Ada.IO_Exceptions.End_Error;
            end if;

            eatWhite (file, eof);

            if Trim (atype, Ada.Strings.Both) = "BOOLEAN" then

                temp        := new booleanattribute;
                temp.name   := aname;
                temp.domain := atype;

                if isprimarykey then
                    temp.isprimarykey := True;
                end if;

            elsif Trim (atype, Ada.Strings.Both) = "STRING" then

                temp        := new stringattribute;
                temp.name   := aname;
                temp.domain := atype;

                if isprimarykey then
                    temp.isprimarykey := True;
                end if;

            elsif Trim (atype, Ada.Strings.Both) = "INTEGER" then

                temp        := new integerattribute;
                temp.name   := aname;
                temp.domain := atype;

                if isprimarykey then
                    temp.isprimarykey := True;
                end if;

            elsif Trim (atype, Ada.Strings.Both) = "DATE" then

                temp        := new dateattribute;
                temp.name   := aname;
                temp.domain := atype;

                if isprimarykey then
                    temp.isprimarykey := True;
                end if;

            else
                Ada.Text_IO.Put_Line ("            unknown type
specified.");
            end if;

            --after eating the white space we should be left at the
',' or
            --the ')'.
            eatWhite (file, eof);

            if not eof then
                Ada.Text_IO.Look_Ahead (file, char, eof);
            else
                raise Ada.IO_Exceptions.End_Error;
            end if;

            --we leave the comma in the stream so that parseAttributes
can
            --pick it up and loop for the next attribute.  We leave
the second
            --')' for parseAttributes to read to know when to exit the
loop and
            --quit parsing attributes.
            if char /= Comma and char /= Right_Parenthesis then
                Ada.Text_IO.Put_Line(
"            Error in input:  Missing ')' after Primary Key
designation or ',' between attributes.")
;
                temp := null;
            end if;

        else
            Ada.Text_IO.Put_Line
               (
"            Error in input file:  Format not correct, no type
specified for attribute " &
                aname);
            temp := null;
        end if;

        return temp.all;

    end parseattribute;

begin

    null;

end parser;


with Ada.Text_IO, Ada.Characters.Latin_1, Ada.Strings.Fixed,
Ada.Strings.Maps, Ada.IO_Exceptions;

use Ada.Characters.Latin_1;

package util is
    type string_ptr is access all String;
    type string_array is array (Integer range <>) of string_ptr;
    type string_array_ptr is access all string_array;

    max_columns              : Integer := 5;
    max_tables               : Integer := 5;
    max_tablename_length     : Integer := 25;
    max_attributename_length : Integer := 25;
    max_stringlength         : Integer := 255;
    max_typename_length      : Integer := 7;
    max_filename_length      : Integer := 45;
    max_index_namelength: integer := 50;

    procedure cls;
    procedure pl (text : in String; newline : in Boolean; setcolumn :
in Boolean := True);
    function tokenize (text : in String) return string_array_ptr;
    procedure eatWhite (fin : in out Ada.Text_IO.File_Type; eof : in
out Boolean);
end util;


package body Util is

    procedure cls is
        i : Integer := 1;
    begin
        while i < 40 loop
            Ada.Text_IO.New_Line;
            i := i + 1;
        end loop;
    end cls;

    procedure pl (text : in String; newline : in Boolean; setcolumn :
in Boolean := True) is
    begin

        if newline then
            if setcolumn then
                Ada.Text_IO.Set_Col (15);
            end if;
            Ada.Text_IO.Put_Line (text);
        elsif setcolumn then
            Ada.Text_IO.Set_Col (15);
            Ada.Text_IO.Put (text);
        else
            Ada.Text_IO.Put (text);
        end if;

    end pl;

    function tokenize (text : in String) return string_array_ptr is
        temp             : string_array_ptr;
        first            : Integer := 1;
        i                : Integer := 1;
        number_of_commas : Integer := 0;
        data             : string_ptr;
        data2            : string_ptr;
    begin
        data             := new String'(text);
        number_of_commas := Ada.Strings.Fixed.Count (data.all,
Ada.Strings.Maps.To_Set (','));

        if number_of_commas > max_columns then
            pl ("Invalid number of columns specified", True);
            raise Ada.IO_Exceptions.Data_Error;
        end if;

        temp := new string_array (1 .. number_of_commas + 1);

        --first will point to the first comma.
        first :=
            Ada.Strings.Fixed.Index
               (data.all,
                Ada.Strings.Maps.To_Set (','),
                Ada.Strings.Inside,
                Ada.Strings.Forward);

        while i <= number_of_commas and number_of_commas < max_columns
loop

            temp.all (i) := new String'(data.all (1 .. first - 1));
            data2        := new String (1 .. data.all'length - first);
            data2.all    := data.all (first + 1 .. data.all'length);
            data         := new String'(data2.all);
            i            := i + 1;
            first        :=
                Ada.Strings.Fixed.Index
                   (data.all,
                    Ada.Strings.Maps.To_Set (','),
                    Ada.Strings.Inside,
                    Ada.Strings.Forward);

        end loop;

        temp.all (i) := new String'(data.all);

        return temp;
    end tokenize;

    --------------------
    --    eatWhite    --
    --------------------
    procedure eatWhite (fin : in out Ada.Text_IO.File_Type; eof : in
out Boolean) is
        char : Character;
    begin

        Ada.Text_IO.Look_Ahead (fin, char, eof);

        while Ada.Text_IO.End_Of_Line (fin) and not
Ada.Text_IO.End_Of_File (fin) loop
            Ada.Text_IO.Skip_Line (fin);
        end loop;

        Ada.Text_IO.Look_Ahead (fin, char, eof);

        while (char = Space or char = HT or char = LF or char = CR)
and
              not Ada.Text_IO.End_Of_File (fin)
        loop

            Ada.Text_IO.Get (fin, char);

            while Ada.Text_IO.End_Of_Line (fin) and not
Ada.Text_IO.End_Of_File (fin) loop
                Ada.Text_IO.Skip_Line (fin);
            end loop;

            Ada.Text_IO.Look_Ahead (fin, char, eof);
        end loop;

    end eatWhite;

begin
    null;
end Util;


with util, Ada.Calendar, attribute_types, Ada.Streams.Stream_IO;

use util, attribute_types;

package schema_types is

    ---------------------------------
    --    Variable Declarations    --
    ---------------------------------
    fin  : Ada.Streams.Stream_IO.File_Type;
    fout : Ada.Streams.Stream_IO.File_Type;

    type schema (number_of_attributes : Integer) is tagged record
        tablename : String (1 .. max_tablename_length) := (1 ..
max_tablename_length => ' ');
        attributes        : attribute_array (1 ..
number_of_attributes);
        byte_start        : Integer := 0;
        byte_end          : Integer := 0;
        primary_key_count : Integer := 0;
    end record;
    type schema_ptr is access all schema'class;
    type schema_array is array (Integer range <>) of schema_ptr;
    type schema_array_ptr is access all schema_array;
    type tuple is array (Integer range <>) of attribute_array_ptr;
    type tuple_ptr is access all tuple;

    procedure createtable (schemainfo : schema_ptr);
    function loadtable (sname : String) return schema_ptr;
    function findrecord (schemainfo : schema; values :
attribute_array) return Integer;
    procedure insertrec (schemainfo : schema; values :
attribute_array);
    procedure deleterec (schemainfo : schema; primary_key_values :
attribute_array);
    procedure updaterec
       (schemainfo : schema;
        pkattribs  : attribute_array;
        values     : attribute_array);
    function selectrec (schemainfo : schema) return tuple_ptr;

end schema_types;


with Ada.Streams.Stream_IO, Ada.Calendar, GNAT.Calendar.Time_IO,
Ada.Text_IO, Ada.Strings.Fixed,
 Ada.Directories, Ada.IO_Exceptions;
use Ada.Streams.Stream_IO, Ada.Calendar, GNAT.Calendar.Time_IO,
Ada.Strings.Fixed;

package body schema_types is

    procedure createtable (schemainfo : schema_ptr) is
        fout     : File_Type;
        attribs  : attribute_array_ptr;
        attribs2 : attribute_array_ptr;
        i        : Integer := 1;
        ii       : Integer := 1;
        temp     : access attribute'class;
    begin

        if schemainfo = null then
            return;
        end if;

        --  put them in order first
        for x in  1 .. schemainfo.attributes'length loop
            for y in  x + 1 .. schemainfo.attributes'length loop

                if schemainfo.attributes (y).name <
schemainfo.attributes (x).name then
                    temp                      := schemainfo.attributes
(y);
                    schemainfo.attributes (y) := schemainfo.attributes
(x);
                    schemainfo.attributes (x).all := temp.all;
                end if;
            end loop;
        end loop;

        attribs  := new attribute_array (1 ..
schemainfo.attributes'length);
        attribs2 := new attribute_array (1 ..
schemainfo.attributes'length);

        for x in  1 .. schemainfo.attributes'length loop
            if schemainfo.attributes (x).isprimarykey then
                attribs (i) := schemainfo.attributes (x);
                i           := i + 1;
            else
                attribs2 (ii) := schemainfo.attributes (x);
                ii            := ii + 1;
            end if;
        end loop;

        i  := i - 1;
        ii := ii - 1;

        --  the primary_key attributes first
        for x in  1 .. i loop
            schemainfo.attributes (x) := attribs (x);
        end loop;

        --  non-primary key attributes next
        for x in  1 .. ii loop
            schemainfo.attributes (x + i) := attribs2 (x);
        end loop;

        Create (fout, Out_File, Trim (schemainfo.all.tablename,
Ada.Strings.Both));
        --We are writing the number of attributes so that when we load
        --the table we can determine the number of attributes to put
        --into the new, loading schema.
        Integer'write (Stream (fout),
schemainfo.all.attributes'length);

        schemainfo.all.byte_start := Integer'val (Index (fout));

	--we output it once so that we can capture the file position for
byte_end
        schema'output (Stream (fout), schemainfo.all);

	--fill in byte_end
        schemainfo.all.byte_end := Integer'val (Index (fout));

	close(fout);
	Open (fout, Out_File, Trim (schemainfo.all.tablename,
Ada.Strings.Both));

        Integer'write (Stream (fout),
schemainfo.all.attributes'length);

	--now we have byte_start and byte_end
        schema'output (Stream (fout), schemainfo.all);

        for x in  1 .. schemainfo.all.attributes'length loop
	    to_disc(fout, schemainfo.all.attributes(x).all);
        end loop;

        Close (fout);

    end createtable;

    function loadtable (sname : String) return schema_ptr is
        schemainfo : schema_ptr;
        fin        : File_Type;
        length     : Integer;
        position   : integer;
    begin
        Open (fin, In_File, Trim (sname, Ada.Strings.Both));

        Integer'read (Stream (fin), length);

        schemainfo                := new schema (length);
        schemainfo.all            := schema'class'input (Stream
(fin));

	--mark where we are at in the file to start reading attributes.
        position                  := Integer'val (Index (fin));

        for x in  1 .. schemainfo.attributes'length loop
-----------------------------------------------------
-- Old code I plan on removing
-----------------------------------------------------
--              schemainfo.all.attributes (x).all.byte_start :=
position;
--
--              if Trim (schemainfo.all.attributes (x).domain,
Ada.Strings.Both) = "BOOLEAN" then
--  		schemainfo.all.attributes (x)                := new
booleanattribute;
--                  schemainfo.all.attributes (x).all            :=
--                      booleanattribute'input (Stream (fin));
--              elsif Trim (schemainfo.all.attributes (x).domain,
Ada.Strings.Both) = "STRING" then
--                  schemainfo.all.attributes (x)                :=
new stringattribute;
--                  schemainfo.all.attributes (x).all            :=
--                      stringattribute'input (Stream (fin));
--              elsif Trim (schemainfo.all.attributes (x).domain,
Ada.Strings.Both) = "INTEGER" then
--                  schemainfo.all.attributes (x)                :=
new integerattribute;
--                  schemainfo.all.attributes (x).all            :=
--                      integerattribute'input (Stream (fin));
--              else --  "DATE"
--                  schemainfo.all.attributes (x)                :=
new dateattribute;
--                  schemainfo.all.attributes (x).all            :=
--                      dateattribute'input (Stream (fin));
--              end if;
--              position := Integer'val (Index (fin));
--              schemainfo.all.attributes (x).all.byte_end   :=
position;
-- End old code
------------------------------------------------------
-----------------------------------------------------------
-- The code I want to use for dispatching
-----------------------------------------------------------
--  	    schemainfo.all.attributes (x) := new
attribute'class'(from_disc(fin, schemainfo.all.attributes (x).all));
-----------------------------------------------------------

------------------------------------------------------------
-- Debug code below --
------------------------------------------------------------
-- For some reason some of the attributes on schemainfo come through
-- as "unknown" after the schemainfo was filled in from
'input(stream).
-- It doesn't appear to me that createtable procedure in this package
-- writes the schema object incorrectly so I don't understand why
-- the attributes of the schemainfo object we retrieve with 'input are
-- "unknown".  Well, the domain member of the attribute is not one of
-- BOOLEAN, STRING, INTEGER or DATE; that's why it prints it but why
-- isn't the domain member one of those values?

            if Trim (schemainfo.all.attributes (x).domain,
Ada.Strings.Both) = "BOOLEAN" then
ada.text_io.put_line(schemainfo.all.attributes (x).name);
ada.text_io.put_line(schemainfo.all.attributes (x).domain);

            elsif Trim (schemainfo.all.attributes (x).domain,
Ada.Strings.Both) = "STRING" then
ada.text_io.put_line(schemainfo.all.attributes (x).name);
ada.text_io.put_line(schemainfo.all.attributes (x).domain);

	    elsif Trim (schemainfo.all.attributes (x).domain,
Ada.Strings.Both) = "INTEGER" then
ada.text_io.put_line(schemainfo.all.attributes (x).name);
ada.text_io.put_line(schemainfo.all.attributes (x).domain);

            elsif Trim (schemainfo.all.attributes (x).domain,
Ada.Strings.Both) = "DATE" then
ada.text_io.put_line(schemainfo.all.attributes (x).name);
ada.text_io.put_line(schemainfo.all.attributes (x).domain);
	    else
ada.text_io.put_line("unknown");
            end if;
        end loop;

-- End Debug Code
---------------------------------------------------------------
        Close (fin);

        return schemainfo;

    exception
        when Ada.IO_Exceptions.Status_Error =>
            Ada.Text_IO.Put_Line ("Status error in loadtable");
            return null;
    end loadtable;

    ---------------------
    --  INSERT RECORD  --
    ---------------------
    procedure insertrec (schemainfo : schema; values :
attribute_array) is
        location : Integer := -1;
        char     : Character;
    begin

        location := findrecord (schemainfo, values);

        --if the record isn't in there it is -1
        if location = -1 then

            Open (fout, Append_File, Trim (schemainfo.tablename,
Ada.Strings.Both));

            for x in  1 .. schemainfo.attributes'length loop
		to_disc(fout, values (x).all);
            end loop;

            Close (fout);
        else
            pl ("Record already exists with that key", True, True);
            pl ("Press Enter to continue...", True, True);
            Ada.Text_IO.Get_Immediate (char);
        end if;

    end insertrec;

    ---------------------
    --  SELECT RECORD  --
    ---------------------
    function selectrec (schemainfo : schema) return tuple_ptr is
        temp  : attribute_array_ptr;
        recs  : tuple_ptr;
        recs2 : tuple_ptr;
        i     : Integer := 1;

    begin
        Open (fin, In_File, Trim (schemainfo.tablename,
Ada.Strings.Both));
        Set_Index
           (fin,
            Ada.Streams.Stream_IO.Count'val
                (schemainfo.attributes
(schemainfo.attributes'length).all.byte_end));

        temp := new attribute_array (1 ..
schemainfo.attributes'length);

        if End_Of_File (fin) then
            Close (fin);
            return null;
        end if;

        recs := new tuple (1 .. 1);

        while not End_Of_File (fin) loop
            for x in  1 .. temp.all'length loop
		temp(x) := new attribute'class'(from_disc(fin, schemainfo.attributes
(x).all));
            end loop;

            if i < 2 then
                recs (recs'last) := temp;
            else
                recs2 := new tuple (1 .. recs'length);

                for z in  1 .. recs'length loop
                    recs2 (z) := recs (z);
                end loop;

                recs := new tuple (1 .. i);

                for z in  1 .. recs2'length loop
                    recs (z) := recs2 (z);
                end loop;

                recs (recs'last) := temp;
            end if;
            temp := new attribute_array (1 ..
schemainfo.attributes'length);
            i    := i + 1;
        end loop;

        Close (fin);

        return recs;

    end selectrec;

    -------------------
    --  FIND RECORD  --
    -------------------
    function findrecord (schemainfo : schema; values :
attribute_array) return Integer is
        temp         : attribute_array_ptr;
        location     : Ada.Streams.Stream_IO.Count;
        found        : Integer := 0;
        done         : Boolean := False;
        comparrisons : Integer := 0;
    begin

        Open (fin, In_File, Trim (schemainfo.tablename,
Ada.Strings.Both));

        Set_Index
           (fin,
            Ada.Streams.Stream_IO.Count'val
                (schemainfo.attributes
(schemainfo.attributes'length).all.byte_end));
        temp := new attribute_array (1 ..
schemainfo.attributes'length);

        while not End_Of_File (fin) and then not done loop
            --mark our current location in the file.
            location := Index (fin);

            --read the whole line from the file,
            for x in  1 .. schemainfo.attributes'length loop
		temp(x) := new attribute'class'(from_disc(fin,
schemainfo.attributes(x).all));
            end loop;

            --then compare them.
            comparrisons := 0;
            found        := 0;

            for x in  1 .. values'length loop

                if schemainfo.attributes (x).isprimarykey then

                    comparrisons := comparrisons + 1;

                    if Trim (values (x).domain, Ada.Strings.Both) =
"BOOLEAN" then
                        if booleanattribute (temp (x).all).value =
                           booleanattribute (values (x).all).value
                        then
                            found := found + 1;
                        end if;
                        --
ada.text_io.put_line(boolean'image(booleanattribute(temp(x).all).value
                        --));
                    elsif Trim (values (x).domain, Ada.Strings.Both) =
"STRING" then
                        if stringattribute (temp (x).all).value =
                           stringattribute (values (x).all).value
                        then
                            found := found + 1;
                        end if;
                        --
ada.text_io.put_line(stringattribute(temp(x).all).value);
                    elsif Trim (values (x).domain, Ada.Strings.Both) =
"INTEGER" then
                        if integerattribute (temp (x).all).value =
                           integerattribute (values (x).all).value
                        then
                            found := found + 1;
                        end if;
                        --
ada.text_io.put_line(integer'image(integerattribute(temp(x).all).value
                        --));
                    else -- "DATE"
                        if dateattribute (temp (x).all).value =
                           dateattribute (values (x).all).value
                        then
                            found := found + 1;
                        end if;
                        --
ada.text_io.put_line(image(dateattribute(temp(x).all).value,
                        --iso_date));
                    end if;
                end if;
            end loop;

            if found = comparrisons and then comparrisons > 0 then
                done := True;
            end if;

            if End_Of_File (fin) then
                done := True;
            end if;
        end loop;

        Close (fin);

        if found < comparrisons then
            return -1;
        elsif found = 0 and then comparrisons = 0 then
            return -1;
        else
            return Integer'val (location);
        end if;

    end findrecord;

    ---------------------
    --  DELETE RECORD  --
    ---------------------
    procedure deleterec (schemainfo : schema; primary_key_values :
attribute_array) is
        location          : Integer;
        original_byte_end : Integer := schemainfo.attributes
(schemainfo.attributes'last).byte_end;
        temp              : attribute_array_ptr;
        char              : Character;
    begin
        location := findrecord (schemainfo, primary_key_values);

        --If findrecord seeks past the schema info header in the file
and ends
        --on the end of file it will return -1.  Therefore, no records
to delete
        --in the file.
        if location = -1 then
            pl ("No records to delete with that key", True, True);
            pl ("Press Enter to continue...", True, True);
            Ada.Text_IO.Get_Immediate (char);
            return;
        end if;

        Create (fout, Out_File, "swapfile");
        Open (fin, In_File, Trim (schemainfo.tablename,
Ada.Strings.Both));

        --output the schema header information to the file
        Integer'write (Stream (fout), schemainfo.attributes'length);

	--I took these out so that we could create a function for
	--updating records that returns an rrn.  functions do not
	--allow out mode parameters and deleterec had an out mode
	--parameter because of this next line.
        --schemainfo.byte_start := Integer'val (Index (fout));
        schema'output (Stream (fout), schemainfo);

	--I took these out so that we could create a function for
	--updating records that returns an rrn.  functions do not
	--allow out mode parameters and deleterec had an out mode
	--parameter because of this next line.
        --schemainfo.byte_end := Integer'val (Index (fout));

        for x in  1 .. schemainfo.attributes'length loop

		to_disc(fout, schemainfo.attributes(x).all);
        end loop;

        --set the index on the input file so we skip the header on
input file.
        Set_Index (fin, Ada.Streams.Stream_IO.Count'val
(original_byte_end));
        temp := new attribute_array (1 ..
schemainfo.attributes'length);

        --Read records from one file and insert them into the other
file until
        --we get to the location of the record we want to delete.
        while Index (fin) < Ada.Streams.Stream_IO.Count'val (location)
loop

            for x in  1 .. temp.all'length loop
		temp(x) := new attribute'class'(from_disc(fin,
schemainfo.attributes(x).all));
		to_disc(fin, temp(x).all);
            end loop;
        end loop;

        --do a blank read to move past the line to delete
        for x in  1 .. schemainfo.attributes'length loop

	    temp(x) := new attribute'class'(from_disc(fin,
schemainfo.attributes(x).all));
        end loop;

	--output the rest of the records.
        while not End_Of_File (fin) loop
            for x in  1 .. temp.all'length loop
		temp(x) := new attribute'class'(from_disc(fin,
schemainfo.attributes(x).all));
		to_disc(fout, temp(x).all);
            end loop;
        end loop;

        Close (fin);
        Close (fout);
        Ada.Directories.Delete_File (Trim (schemainfo.tablename,
Ada.Strings.Both));
        Ada.Directories.Rename ("swapfile", Trim
(schemainfo.tablename, Ada.Strings.Both));

        location := findrecord (schemainfo, primary_key_values);

        if location >= 1 then
            deleterec (schemainfo, primary_key_values);
        end if;

    end deleterec;

    ---------------------
    --  UPDATE RECORD  --
    ---------------------
    procedure updaterec
       (schemainfo : schema;
        pkattribs  : attribute_array;
        values     : attribute_array)
    is
        position : Integer := 0;
        char     : Character;
    begin
        position := findrecord (schemainfo, pkattribs);

        --if the record doesn't exist then insert it
        if position < 1 then
            pl ("That record doesn't exist in the database.", True,
True);
            pl ("Insert it instead (menu item 1).", True, True);
            pl ("Press Enter to continue...", True, True);
            Ada.Text_IO.Get_Immediate (char);
        elsif position >= 1 then
            deleterec (schemainfo, pkattribs);
            insertrec (schemainfo, values);
        end if;
    end updaterec;

begin
    null;
end schema_types;


with util, Ada.Calendar, ada.streams.stream_io;

use util, Ada.Calendar, ada.streams.stream_io;

package attribute_types is

    -----------------------------------
    --    Forwarding Declarations    --
    -----------------------------------
    type attribute is abstract tagged;
    type booleanattribute is tagged;
    type integerattribute is tagged;
    type stringattribute is tagged;
    type dateattribute is tagged;

    --------------------------------------
    --    Attribute Type Declarations    --
    --------------------------------------
    type attribute is abstract tagged record
        name         : String (1 .. max_attributename_length) :=
           (1 .. max_attributename_length => ' ');
        domain       : String (1 .. max_typename_length) := (1 ..
max_typename_length => ' ');
        isprimarykey : Boolean                                :=
False;
        byte_start   : Integer                                := 0;
        byte_end     : Integer                                := 0;
    end record;

    --------------------------------------
    --    Basic Pointer Declarations    --
    --------------------------------------
    type attribute_ptr is access attribute'class;
    type attribute_array is array (Integer range <>) of access
attribute'class;
    type attribute_array_ptr is access all attribute_array;

    procedure to_disc (fout: file_type; item: in out attribute) is
abstract;
    function from_disc(fout: file_type; item: attribute) return
attribute'class is abstract;


    -----------------------------------
    --    Extended Attribute Types   --
    -----------------------------------
    type booleanattribute is new attribute with record
        value : Boolean := False;
    end record;
    type booleanattribute_ptr is access all booleanattribute'class;
    procedure to_disc (fout: file_type; item: in out
booleanattribute);
    function from_disc(fin: file_type; item: booleanattribute) return
attribute'class;

    type integerattribute is new attribute with record
        value : Integer := 0;
    end record;
    type integerattribute_ptr is access all integerattribute'class;
    procedure to_disc (fout: file_type; item: in out
integerattribute);
    function from_disc(fin: file_type; item: integerattribute) return
attribute'class;

    type stringattribute is new attribute with record
        value : String (1 .. max_stringlength) := (1 ..
max_stringlength => ' ');
    end record;
    type stringattribute_ptr is access all stringattribute'class;
    procedure to_disc (fout: file_type; item: in out stringattribute);
    function from_disc(fin: file_type; item: stringattribute) return
attribute'class;

    type dateattribute is new attribute with record
        year  : Year_Number  := 1901;
        month : Month_Number := 1;
        day   : Day_Number   := 1;
        value : Time         := Time_Of (1901, 1, 1);
    end record;
    type dateattribute_ptr is access all dateattribute'class;
    procedure to_disc (fout: file_type; item: in out dateattribute);
    function from_disc(fin: file_type; item: dateattribute) return
attribute'class;

end attribute_types;


with ada.text_io, util, ada.calendar;
use util, ada.calendar;

package body attribute_types is

    procedure to_disc (fout: file_type; item: in out booleanattribute)
is
    begin
        item.byte_start := Integer'val (Index (fout));
        item.byte_end := Integer'val (Index (fout)) +
(booleanattribute'size / 8) - 7;
        booleanattribute'class'output(Stream(fout), item);
    end to_disc;

    function from_disc(fin: file_type; item: booleanattribute) return
attribute'class is
        temp : access attribute'class;
    begin
      temp := new booleanattribute;
      temp.all := booleanattribute'class'input (Stream (fin));
      return temp.all;
    end from_disc;

    procedure to_disc (fout: file_type; item: in out integerattribute)
is
    begin
        item.byte_start := Integer'val (Index (fout));
        item.byte_end := Integer'val (Index (fout)) +
(integerattribute'size / 8) - 7;
        integerattribute'class'output(Stream(fout), item);
    end to_disc;

    function from_disc(fin: file_type; item: integerattribute) return
attribute'class is
    	temp : access attribute'class;
    begin
  	temp := new integerattribute;
	temp.all := integerattribute'class'input (Stream (fin));
	return temp.all;
    end from_disc;

    procedure to_disc (fout: file_type; item: in out stringattribute)
is
    begin
        item.byte_start := Integer'val (Index (fout));
        item.byte_end := Integer'val (Index (fout)) +
(stringattribute'size / 8) - 7;
        stringattribute'class'output(Stream(fout), item);
    end to_disc;

    function from_disc(fin: file_type; item: stringattribute) return
attribute'class is
    	temp: access attribute'class;
    begin
  	temp := new stringattribute;
	temp.all := stringattribute'class'input (Stream (fin));
	return temp.all;
    end from_disc;

    procedure to_disc (fout: file_type; item: in out dateattribute) is
    begin
        item.byte_start := Integer'val (Index (fout));
        item.byte_end := Integer'val (Index (fout)) +
(dateattribute'size / 8) - 11;
        dateattribute'class'output(Stream(fout), item);
    end to_disc;

    function from_disc(fin: file_type; item: dateattribute) return
attribute'class is
    	temp: access attribute'class;
    begin
    	temp := new dateattribute;
	temp.all := dateattribute'class'input (Stream (fin));
	return temp.all;
    end from_disc;

begin
    null;
end attribute_types;


with Ada.Streams.Stream_IO, util, attribute_types,Ada.Calendar; use
util, attribute_types,Ada.Calendar;

package index_types is

    ---------------------------------
    --    Variable Declarations    --
    ---------------------------------
    fin  : Ada.Streams.Stream_IO.File_Type;
    fout : Ada.Streams.Stream_IO.File_Type;
--------------------------------------------------------
--  THIS FILE IS NOT COMPLETE NOR USED YET!!!
--  IT IS INCLUDED BECAUSE IT IS WITH'D
--------------------------------------------------------
    --an index is a file
    --it contains the primary key value and file position for the
primary key for a primary index
	    --the spec sounds like only one attribute will make up a primary
key.
    --for a secondary index it contains an attribute and a position.
	    --The spec says only one attribute.
    --primary indexes are named after the table it belongs to
<tablename>_PIDX
    --secondary indexes are named after the table it belongs to like
<tablename>_SIDX

    --each schema object has a list of index names for a table
	    --initially the list of index names is empty
    --the user adds an index to the table and then the index name goes
into the list of indexes on
    --the schema
    --the schema information will have to be re-written to the table
file when an index is added.
	    --This is the same for the secondary indexes
    --if a tuple that an index is based on is inserted, deleted or
updated then the index must be
    --loaded and re-created.
    ----on updates we only have to change the index if the index value
is being changed.

--The attributes store the name of an index on itself.  When we load
the schema
--we go through each attribute and determine if it is indexed then
load that
--index if it is.  This gives us the "type" on the index value,
elleviates the
--need to maintain a list of index names in the schema object,
----what do we load an index into?


    --There are two types of indexes: primary and secondary
    --** note ** the primary index is just like the secondary; it only
has one entry per item
    --because there is only
    --one item allowed per entry due to the fact that primary keys are
unique.
    --The differences in indexes are:
    ----if we remove a value from a secondary we must match the rrn to
remove the correct
    --item; with a primary key there is only one to remove.
    ----when finding a record, with a primary index when we find the
value we don't
    ----have to search a bunch of records for the exact tuple match.
With secondary
    ----, because there are multiple values that are the same with
different rrn's
    ----we have to search each rrn and compare values to match the
tuple.

    --we don't sort as we read the table, we read the table and then
sort the index file.

    type index is abstract tagged record
        filename : String (1 .. max_index_namelength);
        rrn  : Ada.Streams.Stream_IO.Count := 0;
    end record;
    type index_ptr is access all index;
    type index_array is array (Integer range <>) of index_ptr;

    type booleanindex is tagged record
        key : boolean;
    end record;

    type integerindex is tagged record
        key : integer;
    end record;

    type stringindex is tagged record
        key : string(1..max_stringlength);
    end record;

    type dateindex is tagged record
        key : time;
    end record;
end index_types;


*************************
* Contents of the table.txt file
* This file is used by the main procedure dbprog.
* It must be labeled tables.txt and placed in the
* same directory as the executable dbprog.exe
*************************
T3(
ID(PRIMARY KEY):INTEGER
);

T2(
DATA(PRIMARY KEY):STRING(15)
);

T4(
II(PRIMARY KEY):DATE
);

T1(
mine(PRIMARY KEY):BOOLEAN
);
*************************




^ permalink raw reply	[relevance 3%]

* Re: Char type verification
  2006-11-15 21:57  5% ` Georg Bauhaus
@ 2006-11-15 23:15  0%   ` KE
  0 siblings, 0 replies; 132+ results
From: KE @ 2006-11-15 23:15 UTC (permalink / raw)


Dear George

Many thanks for your detailed answer. I'll most certainly make use of
your advice. However, if you look again, my question was not

- How can I verify whether a character is upper case

Nor was it

- Where, in the library hierarchies of Ada, can I find the character
handling routines

It was intended as "How do you translate this example to Ada? How would
you, as a presumably experienced Ada coder, do it? What hoops would we
jump through?

In other words, I wanted to see some Ada idioms in action to create a
transparent coding of this.

If you believe this simple exercise is not a productive use of your
time, though, I can understand.

Thanks again.


-- KE


Georg Bauhaus wrote:
[snip...]
>
> Or use Ada.Characters.Handling.Is_Upper(c), if you want
> to include characters outside 7bit ASCII.
>
> The C type char, which IIRC might start at -127 or
> at 0, has an implementation defined representation,
> and is a bit vague. The Ada standard frowns upon vague
> things, hence Ada's character type does not have
> theses issues. OTOH, for interfacing with C,
> look at the standard package Interfaces.C.
>
> For more general uses, there are standard packages
> Ada.Strings.Maps, Ada.Strings.Maps.Constants,
> Ada.Characters.Handling, and Ada.Characters.Latin_1.
> There are all kinds of character predicates and
> translation subprograms.
>
> There are variants for Wide_Character, covering
> the BMP of ISO 10646.
> 
> Ada 2005, in addition supports Unicode and related
> subprograms.




^ permalink raw reply	[relevance 0%]

* Re: Char type verification
  @ 2006-11-15 21:57  5% ` Georg Bauhaus
  2006-11-15 23:15  0%   ` KE
  0 siblings, 1 reply; 132+ results
From: Georg Bauhaus @ 2006-11-15 21:57 UTC (permalink / raw)


On Wed, 2006-11-15 at 14:00 -0800, KE wrote:
> Hi
> 
> Assume that I have the following C code:
> 
> #include <stdio.h>
> 
> #define uchar   unsigned char
> 
> 
> static uchar UCASE[] = "ABCDEFGHIJKLMNOPQRSTUVWXYZ";

This is the character range 'A' .. 'Z'.
You can simply write
  c in 'A' .. 'Z'
in any Boolean context where c is of type Character.

Or use Ada.Characters.Handling.Is_Upper(c), if you want
to include characters outside 7bit ASCII.

The C type char, which IIRC might start at -127 or
at 0, has an implementation defined representation,
and is a bit vague. The Ada standard frowns upon vague
things, hence Ada's character type does not have
theses issues. OTOH, for interfacing with C,
look at the standard package Interfaces.C.

For more general uses, there are standard packages
Ada.Strings.Maps, Ada.Strings.Maps.Constants,
Ada.Characters.Handling, and Ada.Characters.Latin_1.
There are all kinds of character predicates and
translation subprograms.

There are variants for Wide_Character, covering
the BMP of ISO 10646.

Ada 2005, in addition supports Unicode and related
subprograms.





^ permalink raw reply	[relevance 5%]

* Re: gnat: can't find package
  2006-10-21 17:03  0%   ` Tim Rowe
@ 2006-10-21 17:54  0%     ` Tim Rowe
  0 siblings, 0 replies; 132+ results
From: Tim Rowe @ 2006-10-21 17:54 UTC (permalink / raw)


Tim Rowe wrote:
> Jeffrey R. Carter wrote:
>> Tim Rowe wrote:
>>> The gnat documentation tells me to expect a package 
>>> Ada.Strings.Maps.Constants, in which I should find
>>> Lower_Set : constant Character_Set;
>>>
>>> It doesn't seem to be there. AdaGIDE doesn't offer "Constants" as a 
>>> completion for "Ada.Strings.Maps.", the compiler doesn't recognise 
>>> Lower_Set, and grep doesn't turn up Lower_Set anywhere in the gnat 
>>> libs directory. Is it anywhere to be found, and if so how do I get 
>>> the compiler to recognise it? And if it isn't, how do I convert a 
>>> string to lower case?
>>
>> This is a standard package. See ARM A.4.6. If you're unable to with 
>> it, there's a problem with your installation.
> 
> That's what I thought. The installation is the one that 
> gnat-3.15p-nt.exe gave me, so if it's not in there then I don't know 
> where I can get it. The other libraries I've tried are in there.

Ok, cancel that. Found it (although AdaGIDE seems to be uncertain about it).



^ permalink raw reply	[relevance 0%]

* Re: gnat: can't find package
  2006-10-21  6:17  0% ` Jeffrey R. Carter
@ 2006-10-21 17:03  0%   ` Tim Rowe
  2006-10-21 17:54  0%     ` Tim Rowe
  0 siblings, 1 reply; 132+ results
From: Tim Rowe @ 2006-10-21 17:03 UTC (permalink / raw)


Jeffrey R. Carter wrote:
> Tim Rowe wrote:
>> The gnat documentation tells me to expect a package 
>> Ada.Strings.Maps.Constants, in which I should find
>> Lower_Set : constant Character_Set;
>>
>> It doesn't seem to be there. AdaGIDE doesn't offer "Constants" as a 
>> completion for "Ada.Strings.Maps.", the compiler doesn't recognise 
>> Lower_Set, and grep doesn't turn up Lower_Set anywhere in the gnat 
>> libs directory. Is it anywhere to be found, and if so how do I get the 
>> compiler to recognise it? And if it isn't, how do I convert a string 
>> to lower case?
> 
> This is a standard package. See ARM A.4.6. If you're unable to with it, 
> there's a problem with your installation.

That's what I thought. The installation is the one that 
gnat-3.15p-nt.exe gave me, so if it's not in there then I don't know 
where I can get it. The other libraries I've tried are in there.



^ permalink raw reply	[relevance 0%]

* Re: gnat: can't find package
  2006-10-21  1:02  5% gnat: can't find package Tim Rowe
  2006-10-21  2:57  0% ` Anh Vo
@ 2006-10-21  6:17  0% ` Jeffrey R. Carter
  2006-10-21 17:03  0%   ` Tim Rowe
  1 sibling, 1 reply; 132+ results
From: Jeffrey R. Carter @ 2006-10-21  6:17 UTC (permalink / raw)


Tim Rowe wrote:
> The gnat documentation tells me to expect a package 
> Ada.Strings.Maps.Constants, in which I should find
> Lower_Set : constant Character_Set;
> 
> It doesn't seem to be there. AdaGIDE doesn't offer "Constants" as a 
> completion for "Ada.Strings.Maps.", the compiler doesn't recognise 
> Lower_Set, and grep doesn't turn up Lower_Set anywhere in the gnat libs 
> directory. Is it anywhere to be found, and if so how do I get the 
> compiler to recognise it? And if it isn't, how do I convert a string to 
> lower case?

This is a standard package. See ARM A.4.6. If you're unable to with it, 
there's a problem with your installation.

-- 
Jeff Carter
"I was hobbling along, minding my own business, all of a
sudden, up he comes, cures me! One minute I'm a leper with
a trade, next minute my livelihood's gone! Not so much as a
'by your leave!' You're cured, mate. Bloody do-gooder!"
Monty Python's Life of Brian
76



^ permalink raw reply	[relevance 0%]

* Re: gnat: can't find package
  2006-10-21  1:02  5% gnat: can't find package Tim Rowe
@ 2006-10-21  2:57  0% ` Anh Vo
  2006-10-21  6:17  0% ` Jeffrey R. Carter
  1 sibling, 0 replies; 132+ results
From: Anh Vo @ 2006-10-21  2:57 UTC (permalink / raw)



Tim Rowe wrote:
> The gnat documentation tells me to expect a package
> Ada.Strings.Maps.Constants, in which I should find
> Lower_Set : constant Character_Set;
>
It is in there. You need to make it visible with dot notation or use
clause. Check the scope and visibility rules from the Ada Language
Reference Manual (LRM).

AV




^ permalink raw reply	[relevance 0%]

* gnat: can't find package
@ 2006-10-21  1:02  5% Tim Rowe
  2006-10-21  2:57  0% ` Anh Vo
  2006-10-21  6:17  0% ` Jeffrey R. Carter
  0 siblings, 2 replies; 132+ results
From: Tim Rowe @ 2006-10-21  1:02 UTC (permalink / raw)


The gnat documentation tells me to expect a package 
Ada.Strings.Maps.Constants, in which I should find
Lower_Set : constant Character_Set;

It doesn't seem to be there. AdaGIDE doesn't offer "Constants" as a 
completion for "Ada.Strings.Maps.", the compiler doesn't recognise 
Lower_Set, and grep doesn't turn up Lower_Set anywhere in the gnat libs 
directory. Is it anywhere to be found, and if so how do I get the 
compiler to recognise it? And if it isn't, how do I convert a string to 
lower case?

TIA,

Tim Rowe



^ permalink raw reply	[relevance 5%]

* Re: programming question . . .
  @ 2006-09-17 23:12  4% ` Martin
  0 siblings, 0 replies; 132+ results
From: Martin @ 2006-09-17 23:12 UTC (permalink / raw)


What compiler/OS are you using?

If you are using GNAT GPL "2005" or "2006" then it comes with
Ada.Directories which will help. For other compilers, try
http://www.martin.dowie.btinternet.co.uk/ and download a version of
Ada.Directories from there. There is a "rename" procedure in this
package.

You could look at using Ada.Strings.Maps for working out the new name
but it's probably overkill. Just loop over the range of the String
object and check/replace as required.

Cheers
-- Martin

lakeoftea wrote:
> I'm trying to write a program that will look at a directory and take
> the "_"'s out of all of the files and replace them with spaces.  this
> seems like an easy program but i haven't used ada since freshman year
> and i'm kind of stumped.  any ideas.  no this is not for an assignment
> :)
> 
> thanks!




^ permalink raw reply	[relevance 4%]

* Re: String filtering
  2005-09-27 11:15  0%       ` David Trudgett
@ 2005-09-27 14:08  6%         ` Georg Bauhaus
  0 siblings, 0 replies; 132+ results
From: Georg Bauhaus @ 2005-09-27 14:08 UTC (permalink / raw)


David Trudgett wrote:

> Yes, well, functions work that way in Ada (fortunately, or
> unfortunately, I don't know). I could have made it a procedure with an
> "in out" parameter, but I like functional programming better.
> Unfortunately, I haven't been able to do proper functional style
> programming in Ada so far, having been thwarted by strong typing and
> lack of "out" parameters in functions.


Here's a filter then.

with Ada.Containers.Vectors;

package Character_Vectors is
   new Ada.Containers.Vectors(Element_Type => Character,
                              Index_Type => Positive);

with Character_Vectors;
with Ada.Strings.Maps.Constants;

procedure filter is

   use Character_Vectors;

   input: Vector;
   output: Vector;


   procedure save_good_ones(c: Cursor) is
      use Ada.Strings.Maps;

      Alpha_Num_Space_Set : constant Character_Set
        := Constants.Alphanumeric_Set or To_Set(' ');
   begin
      if Is_In(Element(c), Alpha_Num_Space_Set) then
         append(output, Element(c));
      end if;
   end save_good_ones;

begin
   Iterate(input, save_good_ones'access);
end filter;



^ permalink raw reply	[relevance 6%]

* Re: String filtering
  2005-09-27  9:49  0%     ` Dmitry A. Kazakov
@ 2005-09-27 11:15  0%       ` David Trudgett
  2005-09-27 14:08  6%         ` Georg Bauhaus
  0 siblings, 1 reply; 132+ results
From: David Trudgett @ 2005-09-27 11:15 UTC (permalink / raw)


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

> On Tue, 27 Sep 2005 19:13:17 +1000, David Trudgett wrote:
>
>>     with Ada.Strings.Maps, Ada.Strings.Unbounded;
>>     use  Ada.Strings.Maps, Ada.Strings.Unbounded;
>> 
>>     Lower_Chars : constant Character_Range := ('a', 'z');
>>     Upper_Chars : constant Character_Range := ('A', 'Z');
>>     Numer_Chars : constant Character_Range := ('0', '9');
>>     Alphanumeric : constant Character_Ranges
>>       := (Lower_Chars, Upper_Chars, Numer_Chars);
>>     Alphanumeric_Set : constant Character_Set := To_Set(Alphanumeric);
>
> with Strings.Maps.Constants;
> use  Strings.Maps.Constants;
>
> -- use defined there Alphanumeric_Set

OK, now I have:

   Alpha_Num_Space_Set : constant Character_Set
     := Alphanumeric_Set or To_Set(' ');

since I realised I also need space.


>
>>     function Strip_Non_Alphanumeric
>>       (Str : in Unbounded_String) return Unbounded_String
>>     is
>>        New_Str : Unbounded_String
>>          := To_Unbounded_String(Count(Str, Alphanumeric_Set));
>
> If you do this, then use String (1..Count (...));

If I did that then I would need to convert back to unbounded_string
when I return the function result. Would that be significantly faster
than working on a pre-allocated unbounded string?


>
>>     begin
>>        New_Str := To_Unbounded_String("");
>
> No need for that, it is initially an empty string.

I at first thought so myself, until I discovered that New_Str was
uninitialised, as it says in the ARM. Hence, I added that line.


>
>>        for Char in 1 .. Length(Str) loop
>>           if Is_In(Element(Str, Char), Alphanumeric_Set) then
>>              Append(New_Str, Element(Str, Char));
>>           end if;
>>        end loop;
>>        return New_Str;
>>     end Strip_Non_Alphanumeric;
>> 
>> Is something like that what y'all do in situations like this?
>
> I don't.
>

> Firstly it is not clear why characters need to be filtered out. Or
> better to say, how did it happen, that you get garbage in a string?

I am sanitising data received over a socket, which may be of any
length. Hence my use of unbounded_string, and my desire to strip out
non-alphanumeric characters.


> Either, you need a character *stream* filtering, 

Possibly, but I'm not using a socket stream interface at the current
time. The socket library I'm using right now doesn't do streams.


> long before you get a string token out of it, or, more realistically
> an error message (exception), should have happened, for example if
> you take some text from a GUI widget.
>
> Secondly, unbounded strings are rarely needed. 

For some definition of 'rarely', I suppose. :-) I'm sure some people
must use them all the time, so it wouldn't be rare for them.

Ada does make it a pain to use unbounded_strings, so it can seem like
a virtue to avoid them, but other languages use them by default, with
no ill-effects to show for it ;-)

Still, in Ada, I do try to use plain fixed strings where they are
sufficient for the purpose.


> Especially in text parsing etc. It is quite uncommon to change a
> string content there. In your example you don't do it either. You
> create a new string. 

Yes, well, functions work that way in Ada (fortunately, or
unfortunately, I don't know). I could have made it a procedure with an
"in out" parameter, but I like functional programming better.
Unfortunately, I haven't been able to do proper functional style
programming in Ada so far, having been thwarted by strong typing and
lack of "out" parameters in functions.


> Also both the source and the result strings have *known* length.

Known but variable, with no particular bounds.


> So you don't need unbounded strings here. Usually, after making some
> trivial analysis like that you'll find out that only 2% or so really
> need to be unbounded.

It seems to me that to use fixed strings here, I would have to convert
the source to a fixed string, do my working on fixed string, then
convert the result to an unbounded string. It sounds like unnecessary
work to me... ;-)  

Thanks for your tips, though, Dmitry, and I'll definitely keep an eye
out for abuse of unbounded_strings.

Cheers,

David



-- 

David Trudgett
http://www.zeta.org.au/~wpower/

Equally, our immoral person must get away with any crimes he
undertakes in the proper fashion, if he is to be outstandingly
immoral; getting caught must be taken to be a sign of incompetence,
since the acme of immorality is to give an impression of morality
while actually being immoral. So we must attribute consummate
immorality to our consummate criminal, and if we are to leave it
intact, we should have him equipped with a colossal reputation for
morality even though he is a colossal criminal. He should be capable
of correcting any mistakes he makes. He must have the ability to argue
plausibly, in case any of his crimes are ever found out, and to use
force wherever necessary, by making use of his courage and strength and
by drawing on his fund of friends and his financial resources.

  -- Plato, in "Republic", 361a-361b, the words of Glaucon.
  



^ permalink raw reply	[relevance 0%]

* Re: String filtering
  2005-09-27  9:13  5%   ` David Trudgett
@ 2005-09-27  9:49  0%     ` Dmitry A. Kazakov
  2005-09-27 11:15  0%       ` David Trudgett
  0 siblings, 1 reply; 132+ results
From: Dmitry A. Kazakov @ 2005-09-27  9:49 UTC (permalink / raw)


On Tue, 27 Sep 2005 19:13:17 +1000, David Trudgett wrote:

>     with Ada.Strings.Maps, Ada.Strings.Unbounded;
>     use  Ada.Strings.Maps, Ada.Strings.Unbounded;
> 
>     Lower_Chars : constant Character_Range := ('a', 'z');
>     Upper_Chars : constant Character_Range := ('A', 'Z');
>     Numer_Chars : constant Character_Range := ('0', '9');
>     Alphanumeric : constant Character_Ranges
>       := (Lower_Chars, Upper_Chars, Numer_Chars);
>     Alphanumeric_Set : constant Character_Set := To_Set(Alphanumeric);

with Strings.Maps.Constants;
use  Strings.Maps.Constants;

-- use defined there Alphanumeric_Set

>     function Strip_Non_Alphanumeric
>       (Str : in Unbounded_String) return Unbounded_String
>     is
>        New_Str : Unbounded_String
>          := To_Unbounded_String(Count(Str, Alphanumeric_Set));

If you do this, then use String (1..Count (...));

>     begin
>        New_Str := To_Unbounded_String("");

No need for that, it is initially an empty string.

>        for Char in 1 .. Length(Str) loop
>           if Is_In(Element(Str, Char), Alphanumeric_Set) then
>              Append(New_Str, Element(Str, Char));
>           end if;
>        end loop;
>        return New_Str;
>     end Strip_Non_Alphanumeric;
> 
> Is something like that what y'all do in situations like this?

I don't.

Firstly it is not clear why characters need to be filtered out. Or better
to say, how did it happen, that you get garbage in a string? Either, you
need a character *stream* filtering, long before you get a string token out
of it, or, more realistically an error message (exception), should have
happened, for example if you take some text from a GUI widget.

Secondly, unbounded strings are rarely needed. Especially in text parsing
etc. It is quite uncommon to change a string content there. In your example
you don't do it either. You create a new string. Also both the source and
the result strings have *known* length. So you don't need unbounded strings
here. Usually, after making some trivial analysis like that you'll find out
that only 2% or so really need to be unbounded.

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



^ permalink raw reply	[relevance 0%]

* Re: String filtering
  @ 2005-09-27  9:13  5%   ` David Trudgett
  2005-09-27  9:49  0%     ` Dmitry A. Kazakov
  0 siblings, 1 reply; 132+ results
From: David Trudgett @ 2005-09-27  9:13 UTC (permalink / raw)


Jacob Sparre Andersen <sparre@nbi.dk> writes:

> David Trudgett wrote:
>
>> I've been puzzling for a little bit over a good way to filter out
>> unwanted characters from a string. In particular, I have an
>> unbounded string and want to filter out of it all characters not in
>> 'a'..'z', 'A'..'Z', '0'..'9'. So far I've only thought of tedious
>> ways to do it. Is there an easy way to do it using the string
>> handling facilities in Ada? I think I almost got there with the idea
>> of using Maps.Character_Set, and so on, but I haven't quite pieced
>> it together yet.
>
> I would probably simply iterate over the elements in the string and
> copy those which a call to "function Is_In (Element : in Character;
> Set : in Character_Set) return Boolean;" indicate to the target
> string.
>
> You could use "function Count (Source : in Unbounded_String; Set : in
> Maps.Character_Set) return Natural;" to preallocate the target string,
> if you're afraid appending to an unbounded string is too slow for your
> purpose.

OK, thanks for those hints. I've come up with the following, which
seems to do the job:

    with Ada.Strings.Maps, Ada.Strings.Unbounded;
    use  Ada.Strings.Maps, Ada.Strings.Unbounded;

    Lower_Chars : constant Character_Range := ('a', 'z');
    Upper_Chars : constant Character_Range := ('A', 'Z');
    Numer_Chars : constant Character_Range := ('0', '9');
    Alphanumeric : constant Character_Ranges
      := (Lower_Chars, Upper_Chars, Numer_Chars);
    Alphanumeric_Set : constant Character_Set := To_Set(Alphanumeric);

    function Strip_Non_Alphanumeric
      (Str : in Unbounded_String) return Unbounded_String
    is
       New_Str : Unbounded_String
         := To_Unbounded_String(Count(Str, Alphanumeric_Set));
    begin
       New_Str := To_Unbounded_String("");
       for Char in 1 .. Length(Str) loop
          if Is_In(Element(Str, Char), Alphanumeric_Set) then
             Append(New_Str, Element(Str, Char));
          end if;
       end loop;
       return New_Str;
    end Strip_Non_Alphanumeric;


Is something like that what y'all do in situations like this?


Cheers,

David



-- 

David Trudgett
http://www.zeta.org.au/~wpower/

Every war, even the most humanely conducted, with all its ordinary
consequences, the destruction of harvests, robberies, the license and
debauchery, and the murder with the justifications of its necessity
and justice, the exaltation and glorification of military exploits,
the worship of the flag, the patriotic sentiments, the feigned
solicitude for the wounded, and so on, does more in one year to
pervert men's minds than thousands of robberies, murders, and arsons
perpetrated during hundreds of years by individual men under the
influence of passion.

    -- Leo Tolstoy, "The Kingdom of God is Within You"




^ permalink raw reply	[relevance 5%]

* Re: Data table text I/O package?
  2005-07-02 10:24  0%     ` Dmitry A. Kazakov
@ 2005-07-06 22:04  0%       ` Randy Brukardt
  0 siblings, 0 replies; 132+ results
From: Randy Brukardt @ 2005-07-06 22:04 UTC (permalink / raw)


"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> wrote in message
news:1vlfc01w9jkzj$.k4rp7yhtuoj3$.dlg@40tude.net...
...
> >      if Ada.Strings.Unbounded.Index (Ada.Strings.Unbounded.Translate
> > (Current.Line, Ada.Strings.Maps.Constants.Lower_Case_Map),
> > Ada.Strings.Unbounded.To_String (Pattern.Line)) /= 0 then
>
> I'm using a table of tokens instead. The string is matched against the
> table for a longest token that matches. And I always use anchored search.
I
> tend to do everything in one pass and Ada fits here well.

That's actually what the above is doing: a single match in a list of
patterns. It usually is inside of a loop.

Some of the matching uses a special Match_Start routine which is cheaper
than Index; but of course that only works because I know how an unbounded
string works, and Ada lets be create a child to use that information.

I'm not certain what you mean by an "anchored search", but I don't expect
that too work too well on e-mail (which is just a mass of text). I do think
it wouldn't have been any harder to have used type String items here instead
of Unbounded_String. The only reason I used Unbounded_String was to see how
easy or hard it really was to use that package - I won't make that mistake
again.

                        Randy.







^ permalink raw reply	[relevance 0%]

* Re: Data table text I/O package?
  2005-07-02  1:54  5%   ` Randy Brukardt
@ 2005-07-02 10:24  0%     ` Dmitry A. Kazakov
  2005-07-06 22:04  0%       ` Randy Brukardt
  0 siblings, 1 reply; 132+ results
From: Dmitry A. Kazakov @ 2005-07-02 10:24 UTC (permalink / raw)


On Fri, 1 Jul 2005 20:54:18 -0500, Randy Brukardt wrote:

> And if you don't know what you are analyzing for, Ada is hardly the
> programming language to be using. (Unless you're a hard-core Ada nut [a
> category that I qualify in]; but then you hardly need advice from this
> group.) You need a much more dynamic language, perhaps even those Unix
> filters.

I think it depends. I have a quite opposite experience. I'm lazy and always
start to write a UNIX script. After a couple of hours fighting with that
mess I note (usually to late) that to write it in Ada (or even in ANSI C)
would take twice as short.

> For instance, there isn't a way to search for an unbounded string in another
> unbounded string. [TF puts pretty much everything into lists of unbounded
> strings, because it's impossible to predict what sort of string lengths
> items will have.] You have to use To_String to convert to a regular string,
> which is ugly (especially without use clauses):

Yes.

All built-in string types should have a common ancestor.
Ada.Strings.Unbounded was and remains an ugly hack.
 
>      if Ada.Strings.Unbounded.Index (Ada.Strings.Unbounded.Translate
> (Current.Line, Ada.Strings.Maps.Constants.Lower_Case_Map),
> Ada.Strings.Unbounded.To_String (Pattern.Line)) /= 0 then

I'm using a table of tokens instead. The string is matched against the
table for a longest token that matches. And I always use anchored search. I
tend to do everything in one pass and Ada fits here well.

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



^ permalink raw reply	[relevance 0%]

* Re: Data table text I/O package?
  @ 2005-07-02  1:54  5%   ` Randy Brukardt
  2005-07-02 10:24  0%     ` Dmitry A. Kazakov
  0 siblings, 1 reply; 132+ results
From: Randy Brukardt @ 2005-07-02  1:54 UTC (permalink / raw)


"Alexander E. Kopilovich" <aek@VB1162.spb.edu> wrote in message
news:mailman.122.1120188122.17633.comp.lang.ada@ada-france.org...
> Randy Brukardt wrote:
...
> You obviosly don't like data very much, but for a scientist that
scientific
> data (often including raw experimental data) is one of the most valuable
> things. It certainly deserves attentive look (at least, from time to
time),
> not just a bureacratic "analysis".

I'm not speaking about data in general (that would be silly), but about it
in the context of Ada programming. (Or have you forgotten the purpose of
this newsgroup?)

It makes perfect sense to look at raw data if you don't know what to analyze
for and you need to find some patterns to give some insight. I suppose there
also is an amount of idle curiousity, too (certainly that happens to me in
these sorts of circumstances -- that's why I might look at web logs or the
results of a game analysis). But I hardly think it makes sense to design
software based on idle curiousity.

And if you don't know what you are analyzing for, Ada is hardly the
programming language to be using. (Unless you're a hard-core Ada nut [a
category that I qualify in]; but then you hardly need advice from this
group.) You need a much more dynamic language, perhaps even those Unix
filters. Its quite possible that Jacob shouldn't be using Ada at all for his
tasks, and thus he's trying to fit a square peg into a round hole.

> > Truthfully, if what you described above is true, you probably ought to
be
> > programming in Perl (ugh) or Python. Because Ada's text processing is
its
> > weak link, and it makes little sense to write any significant amount of
text
> > processing code in Ada.
>
> It would be interesting to hear reply from Robert Dewar to this opinion
about
> text processing capabilities of Ada -:) . Actually, serious text
processing
> is perfectly possible with Ada, and in fact Ada is more suitable for it
than
> Perl. Ada is unsuitable for quick scripting (especially by novice), but it
> is true for all application domains, it is true for numerical computations
> as well as for text processing .

Certainly, serious text processing is *possible* in Ada. (My Trash Finder
spam filter certainly is an extensive text processing application!!) And of
course, the benefits of Ada do apply (particular type checking and good
runtime checks). But, Ada text processing code is just painful to write, and
it's quite hard to read. That's true no matter whether you use plain strings
or unbounded strings.

One of my original intents with TF was to show a good example of Ada code to
non-Ada programmers. But the code got so long-winded that I gave up on that
idea fairly early on. Moreover, the standard routines in
Ada.Strings.Unbounded were just not fast enough in some cases, and I had to
write special routines that understand the internal representation of an
unbounded string. Yuck. (Ada 200Y will help this a bit, at least the
searching has been improved.)

For instance, there isn't a way to search for an unbounded string in another
unbounded string. [TF puts pretty much everything into lists of unbounded
strings, because it's impossible to predict what sort of string lengths
items will have.] You have to use To_String to convert to a regular string,
which is ugly (especially without use clauses):

     if Ada.Strings.Unbounded.Index (Ada.Strings.Unbounded.Translate
(Current.Line, Ada.Strings.Maps.Constants.Lower_Case_Map),
Ada.Strings.Unbounded.To_String (Pattern.Line)) /= 0 then

Even with a use clause for Ada.Strings.Unbounded (in which case you can't
have one for Ada.Strings.Fixed, else things get very ambiguous):
     if Index (Translate (Current.Line,
Ada.Strings.Maps.Constants.Lower_Case_Map), To_String (Pattern.Line) /= 0
then

So, it's possible to write this sort of code in Ada, and get decent
performance, too, but the result isn't particularly readable,
understandable, or maintainable. It's a lot easier to write this in Perl,
although the result would probably be a bit harder to maintain. Not having
used Python, I can't say for sure, but I'd certainly hope that it would be
easier that this to write (and read!) something simple like a
case-insensitive search for a pattern.

If I had used regular strings, the complexity would have been about the
same, just in different places. (In hindsight, I probably wouldn't have used
unbounded strings at all, they just didn't buy enough simplification.)

So, I stand by my statements. There is more than 8,000 lines of text
processing code in TF, all of which looks like this. And all I can say is
that I certainly hope that there is a better way somewhere, even though such
a way isn't really possible for Ada.

                     Randy.






^ permalink raw reply	[relevance 5%]

* Re: Ada bench : count words
  @ 2005-04-01 20:58  5%                                   ` Georg Bauhaus
  0 siblings, 0 replies; 132+ results
From: Georg Bauhaus @ 2005-04-01 20:58 UTC (permalink / raw)


jtg wrote:

>> I think we have tolerated that C guys telling us that Ada is slow for too
>> long time. Game is over! (:-))
>>
> I'm afraid I don't understand. Who is the winner?
> Maybe you meant: The game just begins :-)

Here's another program for the shootout, regular expression
matching. This is the Spitbol patterns version. Maybe the
report printed by the program needs the removal of leeding
spaces in Natural'image?

with
   GNAT.Spitbol.Patterns,
   Ada.Command_Line,
   Ada.Strings.Maps.Constants,
   Ada.Text_IO;

procedure regexmatch is
    use GNAT.Spitbol.Patterns, Ada.Text_IO, Ada.Strings.Maps;
    package Spit renames GNAT.Spitbol;

    dollar_1, dollar_2, dollar_3: Spit.VString;

    Digit: constant Character_Set := Constants.Decimal_Digit_Set;

    D:         constant Pattern := Any(Digit);
    Area_Code: constant Pattern := (D & Fence & D & D) ** dollar_1;
    Exchange:  constant Pattern := (D & D & D) ** dollar_2;
    Last_Four: constant Pattern := (D & D & D & D) ** dollar_3;

         -- Fence: consider "(123 " after two BreakX calls in `re` below

    re: constant Pattern :=
      BreakX(Digit or To_Set('('))  -- scan upto digit or left paren
      & ( '(' & Area_Code & ')'     -- parenthesized area code
           or                       -- or
                Area_Code)          -- just area code
      & ' '                         -- one space
      & Exchange & Any(" -") & Last_Four
      & ( RPos(0) or NotAny(Digit) );  -- at EOL or a non-digit


    type String_Pointer is access String;
    phones: array(1 .. 50) of String_Pointer;

    line_count: Natural;
    match_count: Natural := 0;
    NUM: Natural;


    procedure set_NUM is
       use Ada.Command_Line;
    begin
       NUM := Positive'value(Argument(1));
    exception
       when Constraint_Error => NUM := 1;
    end set_NUM;


    procedure read_lines is
       last: Natural;
       buf: String(1 .. 80);
    begin

       line_count := phones'first;
       loop
          Get_Line(buf, last);
          phones(line_count) := new String'(buf(buf'first .. last));
          line_count := line_count + 1;
       end loop;

    exception
       when End_Error =>
          line_count := line_count - 1;
    end read_lines;




begin
    set_NUM;
    read_lines;
    Anchored_Mode := True;

    while NUM > 0 loop
       NUM := NUM - 1;

       matching:
       for p in phones'first .. line_count loop

          if Match(phones(p).all, re) then
             if NUM = 0 then
                match_count := match_count + 1;
                put_line(Natural'image(match_count)
                         & ": "
                         & "(" & Spit.S(dollar_1) & ") "
                         & Spit.S(dollar_2) & "-" & Spit.S(dollar_3));
             end if;
          end if;
       end loop matching;
    end loop;
end regexmatch;



^ permalink raw reply	[relevance 5%]

* Re: is something wrong with is_subset?!
  2005-03-22 19:39  6% is something wrong with is_subset?! spambox
  2005-03-22 20:03  0% ` Ludovic Brenta
@ 2005-03-22 20:11  0% ` Georg Bauhaus
  1 sibling, 0 replies; 132+ results
From: Georg Bauhaus @ 2005-03-22 20:11 UTC (permalink / raw)


spambox@volja.net wrote:
> Hello. Can anyone explain why all of the following yield "FALSE"?
> 
> with ada.strings.maps; use ada.strings.maps;
> with ada.text_io; use ada.text_io;
> procedure subset is
> begin
>     put_line(is_subset(to_set("foo"), to_set("foo"))'img);
>     put_line(is_subset(to_set("foo"), to_set("bar"))'img);
>     put_line(is_subset(to_set("foobar"), to_set("bar"))'img);
>     put_line(is_subset(to_set("foo"), to_set("foobar"))'img);
> end subset;

I get TRUE and FALSE twice. Which compiler + version are you
using? (GNAT, obviously, by the nonstandard 'img)

Georg 



^ permalink raw reply	[relevance 0%]

* Re: is something wrong with is_subset?!
  2005-03-22 19:39  6% is something wrong with is_subset?! spambox
@ 2005-03-22 20:03  0% ` Ludovic Brenta
  2005-03-22 20:11  0% ` Georg Bauhaus
  1 sibling, 0 replies; 132+ results
From: Ludovic Brenta @ 2005-03-22 20:03 UTC (permalink / raw)


 writes:
> Hello. Can anyone explain why all of the following yield "FALSE"?
>
> with ada.strings.maps; use ada.strings.maps;
> with ada.text_io; use ada.text_io;
> procedure subset is
> begin
>     put_line(is_subset(to_set("foo"), to_set("foo"))'img);
>     put_line(is_subset(to_set("foo"), to_set("bar"))'img);
>     put_line(is_subset(to_set("foobar"), to_set("bar"))'img);
>     put_line(is_subset(to_set("foo"), to_set("foobar"))'img);
> end subset;
>
> andrej

http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=230809

The gist of it is that you can work around this bug by linking
statically against libgnat.a.

-- 
Ludovic Brenta.



^ permalink raw reply	[relevance 0%]

* is something wrong with is_subset?!
@ 2005-03-22 19:39  6% spambox
  2005-03-22 20:03  0% ` Ludovic Brenta
  2005-03-22 20:11  0% ` Georg Bauhaus
  0 siblings, 2 replies; 132+ results
From: spambox @ 2005-03-22 19:39 UTC (permalink / raw)


Hello. Can anyone explain why all of the following yield "FALSE"?

with ada.strings.maps; use ada.strings.maps;
with ada.text_io; use ada.text_io;
procedure subset is
begin
    put_line(is_subset(to_set("foo"), to_set("foo"))'img);
    put_line(is_subset(to_set("foo"), to_set("bar"))'img);
    put_line(is_subset(to_set("foobar"), to_set("bar"))'img);
    put_line(is_subset(to_set("foo"), to_set("foobar"))'img);
end subset;

andrej

--
http://sonet.homelinux.net




^ permalink raw reply	[relevance 6%]

* Re: Float to String
  2004-11-11 17:36  0%       ` Jeffrey Carter
@ 2004-11-12  0:01  0%         ` David C. Hoos, Sr.
  0 siblings, 0 replies; 132+ results
From: David C. Hoos, Sr. @ 2004-11-12  0:01 UTC (permalink / raw)
  To: Jeffrey Carter; +Cc: comp.lang.ada

No, it is not an error.  Note that the Separators
string contains three characters, blank, plus, and minus.

So, To_Real wants one of those three characters to
separate the mantissa and the exponent.

----- Original Message ----- 
From: "Jeffrey Carter" <spam@spam.com>
Newsgroups: comp.lang.ada
To: <comp.lang.ada@ada-france.org>
Sent: November 11, 2004 11:36 AM
Subject: Re: Float to String


> David C. Hoos, Sr. wrote:
> 
>>   function To_Real
>>     (Representation : String)
>>      return Real
>>   is
>>      Separator   : Natural;
>>      Separators  : constant String := " +-";
> 
> ...
> 
>>      Separator := Ada.Strings.Fixed.Index
>>        (Representation (Representation'First + 1 .. Representation'Last),
>>         Ada.Strings.Maps.To_Set (separators));
>>      if Separator = 0 then
>>         Raise_With_Message;
>>      end if;
> 
> ...
> 
>>   function To_String (Value : Real) return String
> 
> ...
> 
>>         return Mantissa_String & Integer'Image (Exponent);
> 
> Is this an error? To_Real wants a sign on the exponent ('+' or '-') but 
> Integer'Image does not add '+' to non-negative values.
> 
> -- 
> Jeff Carter
> "If a sperm is wasted, God gets quite irate."
> Monty Python's the Meaning of Life
> 56
> 
> _______________________________________________
> comp.lang.ada mailing list
> comp.lang.ada@ada-france.org
> http://www.ada-france.org/mailman/listinfo/comp.lang.ada
> 
>



^ permalink raw reply	[relevance 0%]

* Re: Float to String
  2004-11-11 15:53  5%     ` David C. Hoos, Sr.
@ 2004-11-11 17:36  0%       ` Jeffrey Carter
  2004-11-12  0:01  0%         ` David C. Hoos, Sr.
  0 siblings, 1 reply; 132+ results
From: Jeffrey Carter @ 2004-11-11 17:36 UTC (permalink / raw)


David C. Hoos, Sr. wrote:

>   function To_Real
>     (Representation : String)
>      return Real
>   is
>      Separator   : Natural;
>      Separators  : constant String := " +-";

...

>      Separator := Ada.Strings.Fixed.Index
>        (Representation (Representation'First + 1 .. Representation'Last),
>         Ada.Strings.Maps.To_Set (separators));
>      if Separator = 0 then
>         Raise_With_Message;
>      end if;

...

>   function To_String (Value : Real) return String

...

>         return Mantissa_String & Integer'Image (Exponent);

Is this an error? To_Real wants a sign on the exponent ('+' or '-') but 
Integer'Image does not add '+' to non-negative values.

-- 
Jeff Carter
"If a sperm is wasted, God gets quite irate."
Monty Python's the Meaning of Life
56




^ permalink raw reply	[relevance 0%]

* Re: Float to String
  @ 2004-11-11 15:53  5%     ` David C. Hoos, Sr.
  2004-11-11 17:36  0%       ` Jeffrey Carter
  0 siblings, 1 reply; 132+ results
From: David C. Hoos, Sr. @ 2004-11-11 15:53 UTC (permalink / raw)
  To: Pascal Obry; +Cc: comp.lang.ada

Here is a solution that preserves every bit except the last
bit in the floating point hardware.

The string representation is that of the mantissa expressed
as a decimal integer (with appropriate sign) followed by the
power of the machine radix (2 on a Windows box) by which the
integer must be multiplied to obtain the correct results.

For example, the representation of the value -0.1 (a non-
terminating number in binary is "-14757395258967641294-67".

The representation of the value 0.5 (which can be exactly
represented in binary is "9223372036854775808-64" (remember
the mantissa representation is the decimal equivalent of
a binary 1 followed by 64 zeroes).

The solution is a generic package containing two functions
(To_String and To_Value).  The generic parameter for
instantiation is the floating point type.

For IEEE 32- and 64- bit types, the representation is
exact in all of the cases I've tested.  In the case of
80-bit IEEE, there are occasional differences of one LSB.

So, here it is, along with a test program.  the test program
could be improved by generating a sequence of random numbers,
and keeping track of the worst-case relative difference.

File: precise_real_strings.ads
-----------------------------------------------
generic
   type Real is digits <>;
package Precise_Real_Strings is
   
   function To_String
     (Value : Real) return String;
   
   function To_Real
     (Representation : String) return Real;
   
   Format_Error : exception;
   
end Precise_Real_Strings;

-----------------------------------------------
   

File: precise_real_strings.adb
-----------------------------------------------
   
with Ada.Exceptions;
with Ada.Strings.Fixed;
with Ada.Strings.Maps;
with Interfaces;
package body Precise_Real_Strings is

   procedure Reset;
   pragma Import (C, Reset, "__gnat_init_float");
   --  We import the floating-point processor reset routine so that we can
   --  be sure the floating-point processor is properly set for conversion
   --  calls (see description of Reset in GNAT.Float_Control (g-flocon.ads).
   --  This is notably need on Windows, where calls to the operating system
   --  randomly reset the processor into 64-bit mode.

   -------------
   -- To_Real --
   -------------

   function To_Real
     (Representation : String)
      return Real
   is
      Separator   : Natural;
      Separators  : constant String := " +-";
      Sign_pos    : Natural;
      Exponent    : Integer;
      Mantissa    : Interfaces.Unsigned_64;
      Is_Negative : Boolean;
      procedure Raise_With_Message is
      begin
         Ada.Exceptions.Raise_Exception
           (Format_Error'Identity,
            "Invalid representation: """ & Representation & """.");
      end;
   begin
      Reset;
      Separator := Ada.Strings.Fixed.Index
        (Representation (Representation'First + 1 .. Representation'Last),
         Ada.Strings.Maps.To_Set (separators));
      if Separator = 0 then
         Raise_With_Message;
      end if;
      begin
         Exponent := Integer'Value
           (Representation (Separator .. Representation'Last));
      exception
         when others =>
            Raise_With_Message;
      end;
      Sign_pos := Ada.Strings.Fixed.Index
        (Representation (Representation'First .. Separator - 1),
         Ada.Strings.Maps.To_Set ('-'));
      Is_Negative := Sign_Pos /= 0;
      Mantissa := Interfaces.Unsigned_64'Value
        (Representation (Sign_Pos + 1 .. Separator - 1));
      declare
         Result : Real := Real'Scaling (Real (Mantissa), Exponent);
      begin
         if Sign_Pos = 0 then
            return Result;
         else
            return - Result;
         end if;
      end;
   end To_Real;

   ---------------
   -- To_String --
   ---------------

   function To_String (Value : Real) return String
   is
      Exponent : Integer;
      Mantissa : Interfaces.Unsigned_64;
      Sign     : Character;
   begin
      Reset;
      if Value < 0.0 then
         Sign := '-';
      else Sign := ' ';
      end if;
      Exponent := Real'Exponent (Value) -Real'Machine_Mantissa;
      Mantissa := Interfaces.Unsigned_64
        (Real'Scaling (abs (Value), - Exponent));
      declare
         Mantissa_String : String := Interfaces.Unsigned_64'Image (Mantissa);
      begin
         Mantissa_String (1) := Sign;
         return Mantissa_String & Integer'Image (Exponent);
      end;
   end To_String;

end Precise_Real_Strings;

-----------------------------------------------

File: test_precise_real_strings.adb
-----------------------------------------------
with Ada.Text_IO;
with Precise_Real_Strings;
procedure Test_Precise_Real_Strings
is
   package Llf is new Precise_Real_Strings (Long_Long_Float);
   package Lf is new Precise_Real_Strings (Long_Float);
   package F is new Precise_Real_Strings (Float);
begin
   declare
      Representation : String := Llf.To_String (-0.1);
   begin
      Ada.Text_IO.Put_Line (Representation);
      Ada.Text_IO.Put_Line
        (Long_Long_Float'Image
         (Llf.To_Real (Representation)));
      Representation (1) := '+';
      Ada.Text_IO.Put_Line
        (Long_Long_Float'Image
         (Llf.To_Real (Representation)));
      Representation (1) := ' ';
      Ada.Text_IO.Put_Line
        (Long_Long_Float'Image
         (Llf.To_Real (Representation)));
      Ada.Text_IO.Put_Line
        ("Relative difference:" & Long_Long_Float'Image
        ((Llf.To_Real (Representation) - 0.1)/ 0.1));
      Ada.Text_IO.Put_Line
        ("Precise match? " &
         Boolean'Image (Llf.To_Real (Representation) = 0.1));
   end;
   Ada.Text_IO.New_Line;
   declare
      Representation : String := Lf.To_String (-0.1);
   begin
      Ada.Text_IO.Put_Line (Representation);
      Ada.Text_IO.Put_Line
        (Long_Float'Image
         (Lf.To_Real (Representation)));
      Representation (1) := '+';
      Ada.Text_IO.Put_Line
        (Long_Float'Image
         (Lf.To_Real (Representation)));
      Representation (1) := ' ';
      Ada.Text_IO.Put_Line
        (Long_Float'Image
         (Lf.To_Real (Representation)));
      Ada.Text_IO.Put_Line
        ("Relative difference:" & Long_Float'Image
        ((Lf.To_Real (Representation) - 0.1)/ 0.1));
      Ada.Text_IO.Put_Line
        ("Precise match? " &
         Boolean'Image (Lf.To_Real (Representation) = 0.1));
   end;
   Ada.Text_IO.New_Line;
   declare
      Representation : String := F.To_String (-0.1);
   begin
      Ada.Text_IO.Put_Line (Representation);
      Ada.Text_IO.Put_Line
        (Float'Image
         (F.To_Real (Representation)));
      Representation (1) := '+';
     Ada.Text_IO.Put_Line
        (Float'Image
         (F.To_Real (Representation)));
      Representation (1) := ' ';
      Ada.Text_IO.Put_Line
        (Float'Image
         (F.To_Real (Representation)));
      Ada.Text_IO.Put_Line
        ("Relative difference:" & Float'Image
        ((F.To_Real (Representation) - 0.1)/ 0.1));
      Ada.Text_IO.Put_Line
        ("Precise match? " &
         Boolean'Image (F.To_Real (Representation) = 0.1));
   end;
   Ada.Text_IO.New_Line;
end;

-----------------------------------------------

Here are the results of ruinning the test program:

-14757395258967641294-67
-1.00000000000000000E-01
 1.00000000000000000E-01
 1.00000000000000000E-01
Relative difference: 6.77626357803440271E-20
Precise match? FALSE

-7205759403792794-56
-1.00000000000000E-01
 1.00000000000000E-01
 1.00000000000000E-01
Relative difference: 0.00000000000000E+00
Precise match? TRUE

-13421773-27
-1.00000E-01
 1.00000E-01
 1.00000E-01
Relative difference: 0.00000E+00
Precise match? TRUE

----- Original Message ----- 
From: "Pascal Obry" <pascal@obry.org>
Newsgroups: comp.lang.ada
To: <comp.lang.ada@ada-france.org>
Sent: November 11, 2004 6:32 AM
Subject: Re: Float to String


> 
> tmoran@acm.org writes:
> 
>>   The cosine here is presumably a large integer divided by the square root
>> of the product of two large integers.  How about just writing the three
>> integers, so the external representation is completely accurate.  Then let
>> the reader calculate the square root and division, thus generating as
>> accurate a float as it possibly can, given its hardware.
> 
> Hum, I don't think this is an option for me with the current design.
> 
> Pascal.
> 
> -- 
> 
> --|------------------------------------------------------
> --| Pascal Obry                           Team-Ada Member
> --| 45, rue Gabriel Peri - 78114 Magny Les Hameaux FRANCE
> --|------------------------------------------------------
> --|              http://www.obry.org
> --| "The best way to travel is by means of imagination"
> --|
> --| gpg --keyserver wwwkeys.pgp.net --recv-key C1082595
> _______________________________________________
> comp.lang.ada mailing list
> comp.lang.ada@ada-france.org
> http://www.ada-france.org/mailman/listinfo/comp.lang.ada
> 
>



^ permalink raw reply	[relevance 5%]

* Re: Question about Ada.Unchecked_Conversion
    2004-10-29 14:22  6% ` Dmitry A. Kazakov
@ 2004-10-29 15:15  6% ` Nick Roberts
  1 sibling, 0 replies; 132+ results
From: Nick Roberts @ 2004-10-29 15:15 UTC (permalink / raw)


Eric Jacoboni wrote:

> subtype T_Phrase is String(1..Lg_Max);
>    
> type T_S�parateur is (' ', Ht, Lf, ',' ,';', ':', '.', '?', '!');
> for T_S�parateur'Size use Character'Size;
> 
> function Char_To_S�parateur is 
>       new Ada.Unchecked_Conversion(Character, T_S�parateur);
> 
> Ma_Phrase : T_Phrase;
> 
> What i want to do is simply a test like this, in order to find
> characters that are also separators:
> 
> if Char_To_S�parateur(Ma_Phrase(I)) in T_S�parateur then 
>   ...
> end if;
> 
> But this test always fails and i don't understand why. The logic seems
> correct so i suppose it's a misunderstanding of Unchecked_Conversion?

It certainly is a misunderstanding!

Unchecked_Conversion should be used only when you know for sure that
the bit representation of one type will have the meaning you intend
when interpreted as another type. In this case, the bit representation
for type T_S�parateur is likely to be totally different to that of
Standard.Character.

You don't need to use Unchecked_Conversion to convert between one
character type (T_S�parateur) and another (Standard.Character), and
you should not. You need only (and should) use predefined conversion
for this purpose.

However, in order to do the membership test, you do not want to
perform any conversion, because if a value of type Standard.Character
cannot be converted to T_S�parateur, Constraint_Error will be raised.

Instead, for this job, I recommend you use the facilities of the
standard package Ada.Strings.Maps. In this package, there is a type
Character_Set, with the operations you would expect, including
functions which make it easy (usually) to construct a set.

   with Ada.Characters.Latin_1; use Ada.Characters.Latin_1;
   with Ada.Strings.Maps; use Ada.Strings.Maps;
   ...
      S�parateurs: constant Character_Set := 
         To_Set( HT & LF & Space & ",;:.?!" );
   ...
      for i in Ma_Phrase'Range loop
         if Is_In( Ma_Phrase(i), S�parateurs ) then
            ...

There is another possible method, using an array that maps from
characters to a category (indicating some significance to each
character, in this case, whether it is a separator).

   with Ada.Characters.Latin_1; use Ada.Characters.Latin_1;
   ...
      Est_S�parateur: constant array (Character) of Boolean :=
         ( Space | HT | LF |
              ',' | ';' | ':' | '.' | '?' | '!' => True,
           others => False );
   ...
      for i in Ma_Phrase'Range loop
         if Est_S�parateur( Ma_Phrase(i) ) then
            ...

This method might be difficult for testing Wide_Characters, because
of the size of the array, and the type Character_Set can provide more
sophisticated functionality sometimes.

-- 
Nick Roberts



^ permalink raw reply	[relevance 6%]

* Re: Question about Ada.Unchecked_Conversion
  @ 2004-10-29 14:22  6% ` Dmitry A. Kazakov
  2004-10-29 15:15  6% ` Nick Roberts
  1 sibling, 0 replies; 132+ results
From: Dmitry A. Kazakov @ 2004-10-29 14:22 UTC (permalink / raw)


On Fri, 29 Oct 2004 14:46:54 +0200, Eric Jacoboni wrote:

> There is something i've probably not understood about
> Ada.Unchecked_Conversion behavior, despite readings of Barnes and
> RM95.
> 
> To illustrate my pb, let a String in which i want to count
> various separators :
> 
> subtype T_Phrase is String(1..Lg_Max);
>    
> type T_S�parateur is (' ', Ht, Lf, ',' ,';', ':', '.', '?', '!');
> for T_S�parateur'Size use Character'Size;
> 
> function Char_To_S�parateur is 
>       new Ada.Unchecked_Conversion(Character, T_S�parateur);
> 
> Ma_Phrase : T_Phrase;
> 
> What i want to do is simply a test like this, in order to find
> characters that are also separators:
> 
> if Char_To_S�parateur(Ma_Phrase(I)) in T_S�parateur then 
>   ...
> end if;
> 
> But this test always fails and i don't understand why. The logic seems
> correct so i suppose it's a misunderstanding of Unchecked_Conversion?

The semantics of Unchecked_conversion differs from what you seem to imply.
What you want is probably just:

with Ada.Strings.Maps;        use Ada.Strings.Maps;
with Ada.Characters.Latin_1;  use Ada.Characters.Latin_1;
...
Separators : constant Character_Set := To_Set (" .,:!?" & HT & LF);
...
if Is_In (Ma_Phrase (I), Separators) then
   ...
end if;

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



^ permalink raw reply	[relevance 6%]

* Re: variable lenght strings
  @ 2004-10-22  7:38  5%     ` Martin Krischik
  0 siblings, 0 replies; 132+ results
From: Martin Krischik @ 2004-10-22  7:38 UTC (permalink / raw)


Matthew Heaney wrote:

> 
> "Marius Amado Alves" <amado.alves@netcabo.pt> wrote in message
> news:mailman.46.1098398641.10401.comp.lang.ada@ada-france.org...
>>> 1) Is it possible to use Get_Line with Unbounded and/or Bounded
>>> Strings?
>>
>> Not in the standard, but subprograms like those are usually around, e.g.
>> in the GNAT Library, or end up being written in house.
>>
>>> 2) If not, how should usei input be managed when lines length isn't
>>> known a priori?
>>
>> There's a way using the standard Get_Line, explained in AdaPower.
> 
> Mario is probably referring to an article I posted to CLA a few years'
> ago, and which is now archived at the adapower website.
> 
> The basic idea is this:  algorithms that consume input from a stream need
> a
> way a identify when all of the input has been consumed.  Typically this is
> done using a special value that you know is outside the range of normal
> values, e.g.

Well, you do not check for End_Of_File and that means your solution will
fail if the last line is not terminated with CR/LF. And if you want to
process files which have been edited by human beings than you have to care
for that case 

The following version does work. It hast been tested on hundreds of files
all edited by human beings:

package body
   --
   --  String IO Routienes. This are used because
   --  Ada.Strings.Unbounded.Text_IO and GNAT.IO_Aux both have a suttle
   --  little bug.
   --
   AdaCL.Strings.IO
is
   --
   --  Shorten some names.
   --
   package S_U     renames Ada.Strings.Unbounded;
   package S_Maps  renames Ada.Strings.Maps;
   package Latin_1 renames Ada.Characters.Latin_1;
   package IO      renames Ada.Text_IO;

   --  Buffer length. Works for any non-zero value, larger values take
   --  more stack space, smaller values require more recursion.
   BufferSize : constant := 2000;

   --
   --  Well, there are a lot of Get_Line routines around and GNAT
   --  certanly has its onwn, but all those I have seen have suttle bug:
   --  When the last line is not terminated with CR/LF and a multiple
   --  of buffersize long they will throw and end of file exception.
   --
   --  This version need recursion!
   --
   function Get_Line (
      --  File to be read.
      File : in IO.File_Type)
   return
      String
   is
      --  Trace : AdaCL.Trace.Object := AdaCL.Trace.Function_Trace
(AdaCL.Trace.Entity & ':' & AdaCL.Trace.Source);
      --  pragma Unreferenced (Trace);

      Buffer : String (1 .. BufferSize);
      Last   : Natural;
   begin
      IO.Get_Line (
         File => File,
         Item => Buffer,
         Last => Last);

      if Last < Buffer'Last then
         return Buffer (1 .. Last);
      elsif IO.End_Of_File (File) then
         return Buffer;
      else
         return Buffer & Get_Line (File);
      end if;
   end Get_Line;

   --
   --  Well, there are a lot of Get_Line routines around and GNAT
   --  certanly has its onwn, but all those I have seen have suttle bug:
   --  When the last line is not terminated with CR/LF and a multiple
   --  of buffersize long they will throw and end of file exception.
   --
   --  This version uses a loop.
   --
   function Get_Line (
      --  File to be read.
      File : in IO.File_Type)
   return
      S_U.Unbounded_String
   is
      --  Trace : AdaCL.Trace.Object := AdaCL.Trace.Function_Trace
(AdaCL.Trace.Entity & ':' & AdaCL.Trace.Source);
      --  pragma Unreferenced (Trace);

      Retval : S_U.Unbounded_String := S_U.Null_Unbounded_String;
      Item   : String (1 .. BufferSize);
      Last   : Natural;
   begin
      GetWholeLine :
      loop
         IO.Get_Line (
            File => File,
            Item => Item,
            Last => Last);

         S_U.Append (
            Source   => Retval,
            New_Item => Item (1 .. Last));

         exit GetWholeLine when Last < Item'Last
                      or   IO.End_Of_File (File);

      end loop GetWholeLine;

      return Retval;
   end Get_Line;

   --
   --  Get Next Word.
   --
   procedure Get_Word (
      --  File to be read.
      File : in Ada.Text_IO.File_Type;
      --  String into wich the word is to be read
      Item : out String;
      --  Actual amount of characters read.
      Last : out Natural;
      --  Word Delimiters
      Delimiters : in Ada.Strings.Maps.Character_Set := Word_Delimiters)
   is
      --  Trace : AdaCL.Trace.Object := AdaCL.Trace.Function_Trace
(AdaCL.Trace.Entity & ':' & AdaCL.Trace.Source);
      --  pragma Unreferenced (Trace);

      Next_Char : Character := Latin_1.NUL;
   begin
      Last := Item'First;

      Skip_Blanks :
      loop
         IO.Get (File => File,
               Item => Next_Char);

         --  AdaCL.Trace.Write (Integer'Image (Character'Pos (Next_Char)) &
"'" & String'(1 => Next_Char) & "'");

         exit Skip_Blanks when not S_Maps.Is_In (
                               Element => Next_Char,
                               Set     => Delimiters);
      end loop Skip_Blanks;

      Read_Char :
      loop

         if S_Maps.Is_In (Element => Next_Char,
                     Set     => Delimiters)
         then
            Last := Natural'Pred (Last);

            exit Read_Char;
         end if;

         --  AdaCL.Trace.Write (Integer'Image (Character'Pos (Next_Char)) &
"'" & String'(1 => Next_Char) & "'");

         Item (Last) := Next_Char;

         --  AdaCL.Trace.Write (Item (Item'First .. Last));

         Last := Natural'Succ (Last);

         exit Read_Char when Last = Item'Last;

         IO.Get (File => File,
               Item => Next_Char);

      end loop Read_Char;
   end Get_Word;

   --
   --  Get Next Word.
   --
   --  This version uses recursion! The actual version is garanteed to work
   --  up to words 2000 characters.
   --
   function Get_Word (
      --  File to be read.
      File : in IO.File_Type;
      --  Word Delimiters
      Delimiters : in S_Maps.Character_Set := Word_Delimiters)
   return
      String
   is
      --  Trace : AdaCL.Trace.Object := AdaCL.Trace.Function_Trace
(AdaCL.Trace.Entity & ':' & AdaCL.Trace.Source);
      --  pragma Unreferenced (Trace);

      Buffer : String (1 .. BufferSize);
      Last   : Natural;
   begin
      Get_Word (File       => File,
             Item       => Buffer,
             Last       => Last,
             Delimiters => Delimiters);

      if Last < Buffer'Last then
         return Buffer (1 .. Last);
      elsif IO.End_Of_File (File) then
         return Buffer;
      else
         return Buffer & Get_Word (File, Delimiters);
      end if;
   end Get_Word;

   --
   --  Get Next Word.
   --
   --  This version uses a loop. The actual version is garanteed to work
   --  up to words 2000 characters.
   --
   function Get_Word (
      --  File to be read.
      File : in IO.File_Type;
      --  Word Delimiters
      Delimiters : in Ada.Strings.Maps.Character_Set := Word_Delimiters)
   return
      S_U.Unbounded_String
   is
      --  Trace : AdaCL.Trace.Object := AdaCL.Trace.Function_Trace
(AdaCL.Trace.Entity & ':' & AdaCL.Trace.Source);
      --  pragma Unreferenced (Trace);

      Retval : S_U.Unbounded_String := S_U.Null_Unbounded_String;
      Item   : String (1 .. BufferSize);
      Last   : Natural;
   begin
      GetWholeLine : loop
         Get_Word (File       => File,
                Item       => Item,
                Last       => Last,
                Delimiters => Delimiters);

         S_U.Append (Source   => Retval,
                     New_Item => Item (1 .. Last));

         exit GetWholeLine when Last < Item'Last
                      or   IO.End_Of_File (File);

      end loop GetWholeLine;

      return Retval;
   end Get_Word;

end AdaCL.Strings.IO;

With Regards

Martin
-- 
mailto://krischik@users.sourceforge.net
http://www.ada.krischik.com




^ permalink raw reply	[relevance 5%]

* Re: variable lenght strings
  2004-10-21 17:52  6% variable lenght strings fabio de francesco
  @ 2004-10-21 23:05  0% ` Stephen Leake
  1 sibling, 0 replies; 132+ results
From: Stephen Leake @ 2004-10-21 23:05 UTC (permalink / raw)
  To: comp.lang.ada

fmdf@tiscali.it (fabio de francesco) writes:

> 1) Is it possible to use Get_Line with Unbounded and/or Bounded
> Strings?

If you are using GNAT, you can use Ada.Strings.Unbounded.Text_IO.

> 2) If not, how should user input be managed when lines length isn't
> known a priori?

Ada.Text_IO.Get_Line takes a String argument; if it isn't
filled, you can call Ada.Strings.Unbounded on it.

The tricky part is what to do if your initial guess at a max length is
too short. You can write a loop; keep appending chunks of input until
Get_Line returns Last < Item'last.

> <snip stuff about Find_Token>
> 
> Ok, please let me know if the following is the correct usage:

"Correct usage" is whatever works for your application!
> 
> 
> with Ada.Text_IO, Ada.Strings, Ada.Strings.Fixed, 
>     Ada.Strings.Maps, Ada.Strings.Maps.Constants;
> use Ada.Text_IO, Ada.Strings, Ada.Strings.Fixed,
>     Ada.Strings.Maps, Ada.Strings.Maps.Constants;
> 
> procedure Tokenize is
>         
>     S : constant String := ".symbol HP = High_Pressure    "; -- Line A
>     F : Positive := S'First;
>     L : Natural := S'Last;
>     W : String( 1..30 );
>         
> begin
>   loop
>     Find_Token(S(F..L), Alphanumeric_Set or To_Set("_."), Inside, F,
> L);

It would be best to declare a variable to hold Alphanumeric_Set or
To_Set("_.").

>     if L /= 0 then

This could be 'exit when L = 0', but it's really a style issue.

>        Put_Line( Positive'Image( F ) & ( L - F ) * ' ' &
> Natural'Image( L ) );
>          Move( S( F..L ), W );

Named association is better here; I always forget which is the target
and which the source.

>          Put_Line( ' ' & W );
>          F := L + 1;
>          L := S'Last;
>     else 
>        exit;
>     end if;

>   end loop;      
> end Tokenize;
> 
> 
> Is it correct to check the "L" value as a condition to exit the
> loop?

Yes.

-- 
-- Stephe




^ permalink raw reply	[relevance 0%]

* variable lenght strings
@ 2004-10-21 17:52  6% fabio de francesco
    2004-10-21 23:05  0% ` Stephen Leake
  0 siblings, 2 replies; 132+ results
From: fabio de francesco @ 2004-10-21 17:52 UTC (permalink / raw)


Hi,

while studying from "Ada as a 2nd Language" I am having some problem
to cope with Strings (Fixed, Unbounded and Bounded) manipulation and
especially with assigning between different types of them and with
overall with input/output.

1) Is it possible to use Get_Line with Unbounded and/or Bounded
Strings?

2) If not, how should user input be managed when lines length isn't
known a priori?

3) I have to write a program that parses a file in which there are
lines that have to be "tokenized". I didn't find any Find_Token()
usage example on the Book so I wrote a little piece of code in order
to understand the procedure workings on a fixed string (Line A) that
simulates file input.

Think that I am used with C function strtok() and I must say that Ada
Find_Token is much more elegant and not destructive as strtok() is.

Ok, please let me know if the following is the correct usage:


with Ada.Text_IO, Ada.Strings, Ada.Strings.Fixed, 
    Ada.Strings.Maps, Ada.Strings.Maps.Constants;
use Ada.Text_IO, Ada.Strings, Ada.Strings.Fixed,
    Ada.Strings.Maps, Ada.Strings.Maps.Constants;

procedure Tokenize is
        
    S : constant String := ".symbol HP = High_Pressure    "; -- Line A
    F : Positive := S'First;
    L : Natural := S'Last;
    W : String( 1..30 );
        
begin
  loop
    Find_Token(S(F..L), Alphanumeric_Set or To_Set("_."), Inside, F,
L);
    if L /= 0 then
       Put_Line( Positive'Image( F ) & ( L - F ) * ' ' &
Natural'Image( L ) );
         Move( S( F..L ), W );
         Put_Line( ' ' & W );
         F := L + 1;
         L := S'Last;
    else 
       exit;
    end if;
  end loop;      
end Tokenize;


Is it correct to check the "L" value as a condition to exit the loop?


Thank you in advance for any help,

Fabio De Francesco



^ permalink raw reply	[relevance 6%]

* Re: character matching
  @ 2004-08-15 17:21  4%   ` Steve
  0 siblings, 0 replies; 132+ results
From: Steve @ 2004-08-15 17:21 UTC (permalink / raw)


First have a look at the standard library Ada.Characters.Handling
   You'll find goodies such as:

    function Is_Alphanumeric      (Item : in Character) return Boolean;

Then have alook at Ada.Strings.Maps.  There you'll find:

  function Is_In (Element : in Character;
                         Set     : in Character_Set)
  return Boolean;

I always recommend perusing the standard Ada library headers described in
Annex A of the Ada 95 reference manual.  You'll find lots of tools that do
the grunt work for you.

Steve
(The Duck)


"John J" <g_001@hotmail.com> wrote in message
news:uNITc.3402$BA5.883@hydra.nntpserver.com...
> Thanks for the suggestions; however, I'm trying to learn a bit about the
> syntax and capabilities of ADA. Would someone be kind enough to give me
some
> examples of how I can use ADA to character match. ie, different ways I can
> use '*', '&' to successfully recognise words and sentences.
>
> Thanks
>
>





^ permalink raw reply	[relevance 4%]

* Re: questions from a newbie
    2004-07-15 13:45  5% ` Steve
@ 2004-07-15 14:44  5% ` Georg Bauhaus
  1 sibling, 0 replies; 132+ results
From: Georg Bauhaus @ 2004-07-15 14:44 UTC (permalink / raw)


zork <zork@nospam.com> wrote:
: 
: if c in 'A'..'Z' or c in 'a'..'z' or c in '0'..'9' then
: 
: 
: if c in ('A'..'Z', 'a'..'z', '0'..'9') then

This is the purpose of Ada.Strings.Maps etc.
In Ada.Strings.Maps.Constants you will find predefined
Character_Set constant that match yours.

: Also, I know you can do the following:
: 
: type new_type is array(1..20) of string(1..50);
: words : new_type;
: index : integer := 20;
: words (15) (index ..index) := "K";
: 
: however I find that I cannot instead say:
: 
: words(15)(index):="K";
: 
: why is this so?

...(index) denotes a Character, one component of an array,
...(index .. index) denotes an array slice.
The index values can in general be results of computations at
runtime, i.e., ...(n .. m).  What kind of thing other than
an array slice should (n .. m) denote? OTOH, ...(n) where n
is an index value cannot but denote one array component.

: I get a "Type mismatch in assignment statement, continuing"
: error. It does however work when I use words(15)(index):='K'. The rational
: behind this is that (index..index) represents a range - hence a string -
: whereas (index) represents a single character?



^ permalink raw reply	[relevance 5%]

* Re: questions from a newbie
  @ 2004-07-15 13:45  5% ` Steve
  2004-07-15 14:44  5% ` Georg Bauhaus
  1 sibling, 0 replies; 132+ results
From: Steve @ 2004-07-15 13:45 UTC (permalink / raw)


"zork" <zork@nospam.com> wrote in message news:40f684a8@dnews.tpgi.com.au...
> Hi, I just started a course in ada. I just have 2 questions at present.
>
> -------------
> q1) can:
>
> c : character;
>
> if c in 'A'..'Z' or c in 'a'..'z' or c in '0'..'9' then
>    ....
> end if;
>
> be written as something like:
>
> c : character;
>
> if c in ('A'..'Z', 'a'..'z', '0'..'9') then
>    ....
> end if;
> -------------

Not directly, but you can make use the of standard Ada libraries:
  Ada.Strings.Maps
  Ada.Strings.Maps.Constants
and do something like:

  if Is_In( c, Alphanumeric_Set ) then
    ...
  end if;

Since you're a newbie, I recommend you peruse annex A of the Ada 95
reference manual; it describes the predefined language enviroment, which is
basically a list of all of the standard libraries.

You can download a copy from:
    http://www.adaic.org/standards/ada95.html

>
> Also, I know you can do the following:
>
> type new_type is array(1..20) of string(1..50);
> words : new_type;
> index : integer := 20;
> words (15) (index ..index) := "K";
>
> however I find that I cannot instead say:
>
> words(15)(index):="K";
>
> why is this so? I get a "Type mismatch in assignment statement,
continuing"
> error. It does however work when I use words(15)(index):='K'. The rational
> behind this is that (index..index) represents a range - hence a string -
> whereas (index) represents a single character?
>

You answered your own question here.

If you're coming from a different programming language, you may find that
Ada is kind of a "hard ass" about the syntax it will accept.  When you get
over the frustration and find that more programs work correctly after you
get past the compiler, you may never want to go back.

Steve
(The Duck)

> Any insight most helpful.
>
> Cheers,
> zork
>
>





^ permalink raw reply	[relevance 5%]

* Re: types and non-contigous ranges
  2004-02-27 23:59  4%     ` Randy Brukardt
@ 2004-03-01  8:50  0%       ` Erlo Haugen
  0 siblings, 0 replies; 132+ results
From: Erlo Haugen @ 2004-03-01  8:50 UTC (permalink / raw)


Randy Brukardt skrev:
> "Erlo Haugen" <_elh_@_tema_._com_> wrote in message
> news:403ef778$0$128$edfadb0f@dread11.news.tele.dk...
> 
>>I want to use the set/type like  this:
>>My_array : array[Valid_Characters] of something;
>>That excludes the character set, I guess.
> 
> 
> No, that excludes using an array. :-)
> 
> There is no such thing as discontiguous ranges in Ada; you'll have to create
> it yourself somehow. Ada.Strings.Maps is the easiest way for this particular
> case. For the array, I'd just make it an array (Character) of something, and
> just not use the 'invalid' slots. It's hardly worth the effort to do
> anything else unless "something" is very large.
> 
That was my conclusion too. So I create an array(character) of whatever 
and put empty (null) values in the unused positions.
It just seems like a "Non-Ada-ish" way..

-- 
Erlo
-----
Remove underscores from mail address.
The statements and opinions are mine and does not
neccesarily reflect those of my employers




^ permalink raw reply	[relevance 0%]

* Re: types and non-contigous ranges
  2004-02-27  7:53  0%   ` Erlo Haugen
@ 2004-02-27 23:59  4%     ` Randy Brukardt
  2004-03-01  8:50  0%       ` Erlo Haugen
  0 siblings, 1 reply; 132+ results
From: Randy Brukardt @ 2004-02-27 23:59 UTC (permalink / raw)


"Erlo Haugen" <_elh_@_tema_._com_> wrote in message
news:403ef778$0$128$edfadb0f@dread11.news.tele.dk...
> I want to use the set/type like  this:
> My_array : array[Valid_Characters] of something;
> That excludes the character set, I guess.

No, that excludes using an array. :-)

There is no such thing as discontiguous ranges in Ada; you'll have to create
it yourself somehow. Ada.Strings.Maps is the easiest way for this particular
case. For the array, I'd just make it an array (Character) of something, and
just not use the 'invalid' slots. It's hardly worth the effort to do
anything else unless "something" is very large.

               Randy.






^ permalink raw reply	[relevance 4%]

* Re: types and non-contigous ranges
  2004-02-26 16:07  5% ` Dmitry A. Kazakov
@ 2004-02-27  7:53  0%   ` Erlo Haugen
  2004-02-27 23:59  4%     ` Randy Brukardt
  0 siblings, 1 reply; 132+ results
From: Erlo Haugen @ 2004-02-27  7:53 UTC (permalink / raw)


Dmitry A. Kazakov skrev:
> On Thu, 26 Feb 2004 15:17:38 +0100, Erlo Haugen <_elh_@_tema_._com_>
> wrote:
> 
> 
>>Hello everyone,
>>what is the easiest way to define a (sub)type consisting of ranges and 
>>single values?
> 
> 
> Only ranges are allowed.
> 
> 
>>Let me give an example:
>>
>>I want a type, based on character, that contains 'A'..'Z' and '0'..'9'
>>and some single characters like '�','�' and '�'.
>>
>>subtype Valid_Characters is character range 'A'..'Z' ????? and what then??
>>
>>
>>Do I really have list all the values?
> 
> 
> Take a look at Ada.Strings.Maps and Strings.Maps.Constants. They
> provide sets of characters, operations on them and useful constant
> sets like Alphanumeric_Set etc. I think that
> 
> Whatsoever : constant Character_Set :=
>    Decimal_Digit_Set  or
>    To_Set (Character_Range'('A', 'Z')) or
>    To_Set ('�') or
>    To_Set ('�') or
>    To_Set ('�');
> 
> is what you are looking for.

I want to use the set/type like  this:
My_array : array[Valid_Characters] of something;
That excludes the character set, I guess.

-- 
Erlo
-----
Remove underscores from mail address.
The statements and opinions are mine and does not
neccesarily reflect those of my employers




^ permalink raw reply	[relevance 0%]

* Re: types and non-contigous ranges
  @ 2004-02-26 16:07  5% ` Dmitry A. Kazakov
  2004-02-27  7:53  0%   ` Erlo Haugen
  0 siblings, 1 reply; 132+ results
From: Dmitry A. Kazakov @ 2004-02-26 16:07 UTC (permalink / raw)


On Thu, 26 Feb 2004 15:17:38 +0100, Erlo Haugen <_elh_@_tema_._com_>
wrote:

>Hello everyone,
>what is the easiest way to define a (sub)type consisting of ranges and 
>single values?

Only ranges are allowed.

>Let me give an example:
>
>I want a type, based on character, that contains 'A'..'Z' and '0'..'9'
>and some single characters like '�','�' and '�'.
>
>subtype Valid_Characters is character range 'A'..'Z' ????? and what then??
>
>
>Do I really have list all the values?

Take a look at Ada.Strings.Maps and Strings.Maps.Constants. They
provide sets of characters, operations on them and useful constant
sets like Alphanumeric_Set etc. I think that

Whatsoever : constant Character_Set :=
   Decimal_Digit_Set  or
   To_Set (Character_Range'('A', 'Z')) or
   To_Set ('�') or
   To_Set ('�') or
   To_Set ('�');

is what you are looking for.

--
Regards,
Dmitry A. Kazakov
www.dmitry-kazakov.de



^ permalink raw reply	[relevance 5%]

* Re: URGENT: inserting words into an array
  @ 2004-01-09 23:34  4%   ` Craig Carey
  0 siblings, 0 replies; 132+ results
From: Craig Carey @ 2004-01-09 23:34 UTC (permalink / raw)


On 07 Jan 2004 20:48:07 +0100, Pascal Obry <p.obry@wanadoo.fr> wrote:

>
>mmq_2002@onetel.net.uk (Qas) writes:
>
>> but my problem is slighlty different, i have a text file with 20 words
>> seperated by either a space or new line and i want to know how i can
>> insert each word into the array. i know that the maximum length a word
>> will go to is 25 characters, this is what the file looks like:
>
>This looks like home work, right ?
>
>You should try at least to post something, we will not do your home work :)
>

I provide an example as asked for.
The following code demonstrates a cut-down version of my Striunli fast
Strings package (URL below).


----------------------------------------------------------------------

with Ada.Command_Line;
with Ada.Exceptions;
with Ada.Strings.Fixed;
with Ada.Strings.Maps;
with Ada.Text_IO;
with Ada.Unchecked_Deallocation;
with W_Strings;

procedure Inserting_Words is

   pragma Style_Checks ("3abcefhiklmnoprst");   --  GNAT
   package Tio renames Ada.Text_IO;
   package AS renames Ada.Strings;
   package AE renames Ada.Exceptions;
   package SM renames Ada.Strings.Maps;
   package SF renames Ada.Strings.Fixed;
   package CL renames Ada.Command_Line;
   package SW renames W_Strings;

   use type SW.W_Str;
   subtype File_Type is Tio.File_Type;
   IW_ERROR       : exception;

   procedure Open_File (
            Inp_File    : in out File_Type;
            File_Name   : String) is
   begin
      Tio.Open (Inp_File, Mode => Tio.In_File, Name => File_Name);
   exception
      when X : others =>
         Tio.Put_Line ("Error opening file: """ & File_Name &
                  """: " & AE.Exception_Information (X));
         raise IW_ERROR;
   end Open_File;

   procedure Get_Line (Inp_File : File_Type; Line_Out : out SW.W_Str)
   is
      Part        : String (1 .. 32 * 1024);
      Last        : Natural;
   begin
      Tio.Get_Line (Inp_File, Part, Last);
      if Last = Part'Last then
         SW.Assign (Line_Out, Part);
         while Last = Part'Last loop
            Tio.Get_Line (Inp_File, Part, Last);
            SW.Assign (Line_Out, +Line_Out & Part);
         end loop;
         return;
      else
         SW.Assign (Line_Out, Part (1 .. Last));
      end if;
   exception
      when X : others =>
         Tio.Put_Line ("Error reading line" &
                  Tio.Positive_Count'Image (Tio.Line (Inp_File)) &
                  " of file """ & Tio.Name (Inp_File) &
                  """: " & AE.Exception_Information (X));
         raise IW_ERROR;
   end Get_Line;

   type Words_Integer is new Integer;
   type Words_Array is array (Words_Integer range <>) of SW.W_Str;
   type Words_Array_Ptr is access Words_Array;
   Words          : Words_Array_Ptr := new Words_Array (1 .. 8);
   Words_Last     : Words_Integer := 0;

   procedure Lengthen_Words_Arr (New_Len : Words_Integer) is
      procedure Free_Words_Array is new Ada.Unchecked_Deallocation (
                     Object => Words_Array, Name => Words_Array_Ptr);
      New_Lines   : Words_Array_Ptr;
   begin
      if New_Len > Words'Last then
         New_Lines := new Words_Array (1 .. 1 + 2 * Words'Last);
         for K in 1 .. Words_Last loop
            SW.Assign_Fast (New_Lines (K), Words (K));
         end loop;
         Free_Words_Array (Words);
         Words := New_Lines;
      end if;
      Words_Last := New_Len;
   end Lengthen_Words_Arr;

   procedure Binary_Search (
            Words       : Words_Array;
            Key         : String;
            First, Last : out Words_Integer) is
      K        : Words_Integer;
   begin
      First := Words'First;
      Last := Words'Last;
      while First <= Last loop
         K := (First + Last) / 2;
         if    Key < +Words (K) then Last  := K - 1;
         elsif +Words (K) < Key then First := K + 1;
         else return; end if;
      end loop;
   end Binary_Search;

   Inp_File       : Tio.File_Type;
   Line_1         : SW.W_Str;
   WhiteSpace     : constant SM.Character_Sequence := (
            1 => ASCII.HT, 2 => ASCII.LF, 3 => ASCII.VT,
            4 => ASCII.FF, 5 => ASCII.CR, 6 => ' ',
            7 => Character'Val (160));       --  160 = No_Break_Space
   WhiteSpace_Set : constant SM.Character_Set :=
                                             SM.To_Set (WhiteSpace);
   Was_Opened     : Boolean := False;
begin
   if CL.Argument_Count < 1 then
      Tio.Put_Line ("Usage: " & CL.Command_Name & " Input_File_Name");
      return;
   end if;
   Open_File (Inp_File => Inp_File, File_Name => CL.Argument (1));
   Was_Opened := True;
   while not Tio.End_Of_File (Inp_File) loop
      Get_Line (Inp_File => Inp_File, Line_Out => Line_1);
      declare
         Line        : String := +Line_1;
         P1, P2      : Natural := 0;
         Low, High   : Words_Integer;
      begin
         loop
            SF.Find_Token (Source => Line (P2 + 1 .. Line'Last),
                     Set => WhiteSpace_Set, Test => AS.Outside,
                     First => P1, Last => P2);
            exit when P1 > P2;
            Binary_Search (Words (1 .. Words_Last),
                     Line (P1 .. P2), Low, High);
            Lengthen_Words_Arr (New_Len => Words_Last + 1);
            if Low = High + 1 then                          --  Insert
               for J in Low .. Words_Last - 1 loop
                  SW.Assign (Words (J + 1), +Words (J));
               end loop;
            else
               Low := Words_Last;
            end if;
            SW.Assign (Words (Low), Line (P1 .. P2));
            P1 := P2 + 1;
         end loop;
      end;
   end loop;
   Tio.Put_Line ("The table of words:");
   for K in 1 .. Words_Last loop
      Tio.Put_Line (SF."*" (8 - Words_Integer'Image (K)'Length, ' ') &
               Words_Integer'Image (K) & ": """ & (+Words (K) & '"'));
   end loop;
   if Was_Opened then Tio.Close (Inp_File); end if;
exception
   when X : others =>
      if Was_Opened then Tio.Close (Inp_File); end if;
      if "IW_ERROR" /= AE.Exception_Name (X) then raise; end if;
end Inserting_Words;
----------------------------------------------------------------------

with Ada.Finalization;

package W_Strings is

   --  This is a cut-down version of the Striunli Unbounded Strings
   --  package. URL:
   --    http://www.ijs.co.nz/code/ada95_strings_pkg.zip

   Ws_Error          : exception;

   subtype Ws_String is String;
   type Ws_String_Ptr is access Ws_String;

   Ws_Null_String_Ptr  : aliased constant Ws_String_Ptr :=
                                                new String (1 .. 0);

   type W_Str is new Ada.Finalization.Limited_Controlled with
      record
         Len            : aliased Natural := 0;
         Str            : aliased Ws_String_Ptr := Ws_Null_String_Ptr;
         Valid          : aliased Boolean := True;
      end record;

   procedure Assign (Dest : out W_Str; Source : String);

   procedure Assign_Fast (Dest : out W_Str; Source : in out W_Str);

   function "+" (Source : W_Str) return String;

private
   procedure Finalize (Object : in out W_Str);

   function Bump_Up_Size (Old_High, New_High : Natural)
         return Natural;

end W_Strings;
----------------------------------------------------------------------

with Ada.Unchecked_Deallocation;

package body W_Strings is

   procedure Deallocate_String is
      new Ada.Unchecked_Deallocation (Ws_String, Ws_String_Ptr);

   procedure Assign (
            Dest           : out W_Str;
            Source         : Ws_String)
   is
      New_Len     : Natural := Source'Length;
      Length      : Natural;
      Dest_Str    : Ws_String_Ptr renames Dest.Str;
   begin
      if Dest_Str = Ws_Null_String_Ptr then
         if New_Len = 0 then
            goto DONE_2;      --  Don't call Allocate when New_Len = 0
         end if;
         Dest_Str := new String (1 .. New_Len);
      elsif Dest_Str.all'Last < New_Len then
         Length := Bump_Up_Size (Old_High => Dest_Str.all'Last,
                        New_High => New_Len);
         Deallocate_String (Dest_Str);
         Dest_Str := new String (1 .. Length);
      end if;
      Dest.Str (1 .. New_Len) := Source;
      <<DONE_2>>
      Dest.Len := New_Len;
      Dest.Valid := True;
   end Assign;

   procedure Assign_Fast (Dest : out W_Str; Source : in out W_Str)
   is
      LHS      : W_Str renames Dest;
      RHS      : W_Str renames Source;
      TR       : Ws_String_Ptr;
   begin
      TR := LHS.Str;          --  Swap pointers
      LHS.Str := RHS.Str;
      RHS.Str := TR;
      LHS.Len := RHS.Len;
      RHS.Len := 0;           --  LHS.Len is lost which is convenient
      LHS.Valid := RHS.Valid;
      RHS.Valid := False;     --  Warns on attempt to reuse the string
   end Assign_Fast;

   function Bump_Up_Size (Old_High, New_High : Natural) return Natural
   is
      N           : Natural := Natural'Max (New_High, Natural'Max (64,
                              48 + Natural (17 * (Old_High / 10))));
   begin
      return 32 * ((N + (32 - 1)) / 32);
   end Bump_Up_Size;

   procedure Finalize (Object : in out W_Str) is
   begin
      if Object.Str /= (null) then
         if Object.Str /= Ws_Null_String_Ptr then
            Deallocate_String (Object.Str);
         end if;
      end if;
   end Finalize;

   function "+" (Source : W_Str) return String is
   begin
      if not Source.Valid then
         raise Ws_Error;
      end if;
      return Source.Str.all (1 .. Source.Len);
   end "+";

end W_Strings;
----------------------------------------------------------------------


The above sample code didnt need debugging (i.e. it ran first time and
before the 2nd executable was produced).  Being about 155 lines long,
that is similar to what would be expected.




Craig Carey
Ada 95 mailing lists: http://www.ijs.co.nz/ada_95.htm





^ permalink raw reply	[relevance 4%]

* Re: Word counting
  @ 2003-12-11 22:45  5% ` David C. Hoos
  0 siblings, 0 replies; 132+ results
From: David C. Hoos @ 2003-12-11 22:45 UTC (permalink / raw)
  To: wave, comp.lang.ada@ada.eu.org

Here is some code I originally posted On March 8, 2003 which
does the word parsing using the facilites of the Ada language
standard libraries.

The function "Words" returns an array with an element for
each word in the line.  Each array element contains the first
and last indices of each word.  This would make determination
of the length of each word very easy.

package Word_Parser
is

   type Word_Boundaries is record
      First : Positive;
      Last  : Natural;
   end record;

   type Word_Boundaries_Array is
     array (Positive range <>) of Word_Boundaries;

   -- Limitation: No more than 1024 words per text string.
   function Words (Text : String) return Word_Boundaries_Array;

end Word_Parser;
with Ada.Strings.Fixed;
with Ada.Strings.Maps;
package body Word_Parser is

   Whitespace : constant String := ' ' &
     ASCII.Ht & ASCII.Cr & ASCII.LF;
   Punctuation : constant String := ",./?<>:;'""[]{}!@#$%^&*()_+|-=\~~";
   Delimiters : constant Ada.Strings.Maps.Character_Set :=
     Ada.Strings.Maps.To_Set (Whitespace & Punctuation);

   -----------
   -- Words --
   -----------

   function Words (Text : String) return Word_Boundaries_Array
   is
      Word_Boundaries_List : Word_Boundaries_Array (1 .. 1024);
      Word_Count : Natural := 0;
      First : Positive := Text'First;
   begin
      loop
         Ada.Strings.Fixed.Find_Token
           (Source => Text (First .. Text'Last),
            Set    => Delimiters,
            Test   => Ada.Strings.Outside,
            First  => Word_Boundaries_List (Word_Count + 1).First,
            Last   => Word_Boundaries_List (Word_Count + 1).Last);
         exit when Word_Boundaries_List (Word_Count + 1).Last = 0;
         First := Word_Boundaries_List (Word_Count + 1).Last + 1;
         Word_Count := Word_Count + 1;
      end loop;
      return Word_Boundaries_List (1 .. Word_Count);
   end Words;

end Word_Parser;
with Ada.Command_Line;
with Ada.Text_IO;
with Word_Parser;
procedure Test_Word_Parser
is
   File : Ada.Text_IO.File_Type;
   Line : String (1 .. 10240);
   Last : Natural;
   use type Ada.Text_IO.Count;
begin
   if Ada.Command_Line.Argument_Count /= 1 then
      Ada.Text_IO.Put_Line
        (Ada.Text_IO.Standard_Error,
         "USAGE: " & Ada.Command_Line.Command_Name &
         " <text-file-name>");
      Ada.Command_Line.Set_Exit_Status (0);
      return;
   end if;
   Ada.Text_IO.Open
     (File => File,
      Name => Ada.Command_Line.Argument (1),
      Mode => Ada.Text_IO.In_File);
   while not Ada.Text_IO.End_Of_File (File) loop
      Ada.Text_IO.Get_Line
        (Item => Line,
         File => File,
         Last => Last);
      declare
         Word_Boundary_List :
           constant Word_Parser.Word_Boundaries_Array :=
           Word_Parser.Words (Line (Line'First .. Last));
      begin
         Ada.Text_IO.Put_Line
           ("Words in line" &
            Ada.Text_IO.Count'Image (Ada.Text_IO.Line (File) - 1));
         for W in Word_Boundary_List'Range loop
            Ada.Text_IO.Put_Line
              ("""" & Line
               (Word_Boundary_List (W).First ..
                Word_Boundary_List (W).Last) & """");
         end loop;
      end;
   end loop;
end Test_Word_Parser;

----- Original Message ----- 
From: "wave" <mutilation@bonbon.net>
Newsgroups: comp.lang.ada
To: <comp.lang.ada@ada-france.org>
Sent: Thursday, December 11, 2003 4:01 PM
Subject: Word counting


<snip>




^ permalink raw reply	[relevance 5%]

* Re: Clause "with and use"
  2003-11-15 16:15  4%                       ` Gautier Write-only
@ 2003-11-16  0:02  5%                         ` Robert I. Eachus
  0 siblings, 0 replies; 132+ results
From: Robert I. Eachus @ 2003-11-16  0:02 UTC (permalink / raw)


Gautier Write-only wrote:

> Both "use" you cite are not context clauses -> OT, sorry !

Not off topic.  You can have a use Ascii in a context clause without a 
with for Ascii, in fact you CAN'T have a with clause for Ascii.  (Back 
in 1983 a lot of compilers got tripped up on that special case, but 
those bugs are long gone.)  In Ada 83 a context clause had to contain a 
with clause. But in Ada 95 the syntax has changed, so you should be able 
to compile:

use Ascii;
package Foo is
   Bar: Character := Percent;
end Foo;

If not, complain to your compiler vendor.  (Although I think putting the 
use clause inside Foo looks better.)

> BTW, your mention of ASCII is interesting.
> * Ada 83 (and later) implies a non-written "with Standard; use Standard;"
>   - ASCII is subpackage of Standard.

NO! This is almost as bad as what Russ was saying.  There is no implicit 
with clause for Standard.  Try to create a library unit named Integer. 
You can't.   This is because all library units are explicitly nested 
directly within Standard.  This gives names in Standard a preferential 
visibility.  They can't be hidden by a library unit.  And also there is 
no USE visibility for names in Standard, the visibility is direct.  If 
you have a use clause for a package containing a type named Integer, it 
will not become USE visible due to the direct visibility of the Integer 
in Standard.

> * Ada 95 (and later) implies a non-written "with Ada, Ada.Strings;" when you
>   just write "with Ada.Strings.Maps;". Same for all children 
> -> things are not at all 100% explicit in the present standard.

Ask why, or look at the ARG and Ada 9X DR discussions, etc., and you 
will understand why it was done this way.  First there should be no 
confusion about whether there is a with clause for Ada.Strings. You are 
looking at it.  But consider another case:

package Ada.Strings.Maps is... -- A.4.2(3)

In this case, there is an implicit with of Ada.Strings, and with good 
reason.  To make the language easy to use, we need direct visibility of 
names in Ada.Strings within Ada.Strings.Maps.  That is pretty hard for 
the compiler to do correctly without having Ada.Strings as part of the 
context.  But it is not part of the context clause, because of the 
direct visibility issue, just like Standard.  Ada.Strings.Maps is 
conceptually declared within Ada.Strings, which is within Ada, which is 
within Standard.  Direct visibility all the way, and nary a hint of a 
with or use clause.
> 
> * The "[with and ]use" proposal offers the possibility of writing once
>   the name of a package instead of twice when you use "use" in a context clause.

As I said, not a problem, go ahead and push for "with and use" if you 
like it.  But having a use imply a with breaks things.  That model could 
be fixed, but why even try.  If you currently have a text editor macro 
that maps #wau Foo into "with Foo; use Foo;" you can change it to 
generate "with and use Foo;" if the change is approved.  I don't see it 
as a big deal, but different opinions are allowed and expected.

> -> this feature doesn't reduce from 1 to 0 the appearance of a package name
>    like both mentioned above, but from 2 to 1. When the feature is used, the
>    names remain explicit, but without redundance.
> 
> Clearly the contestation about this proposal is just because this is an evolution.
> Existing elements are by default sacred, improvements are by default suscpicious...

No I look at the "with implies use" proposal and get a splitting 
headache when thinking about how it could be worded.  Answer me just one 
little problem, and I might think about it:

use Foo; use Bar;
package...

Now if there is a package Foo and it contains a package Bar, and there 
is a package Bar in the compilation environment, which one do you get if 
any, and why?  If you don't understand the issue, create the specified 
packages and try it with your current Ada compiler.  Then read RM 8.4(6) 
to see why it works the way it does now, and try to rewrite 8.4(6) to 
match the use implies with proposal.  Now do you see why I have a headache?

This is the reason I often seem to say "Yeah, that's nice, why don't you 
propose it," about some proposals and "Forget it, it won't fly," about 
others.  I can be wrong, if someone finds a way to express things.  Some 
ARG members, especially Tucker, are trying to fit earliest deadline 
first scheduling within a priority based model without 
incompatibilities.  It looks like they are pulling it off.  This is very 
nice because, if it works it will allow some tasks (and priority levels) 
to be used for EDF scheduling and other priority levels for ordinary 
priority based scheduing.  But it is a lot of work that may never be 
visible to most Ada users.  The theory will be there, the few 
implementors who need to will understand it, and enough ARG members will 
understand the model to fix it if it breaks.  For something like that, 
it is worth the pain.  To shorten "with and use" to "use"?  No way!

But in this case, "with and use" is simple and seems to address the 
problem without monkeying with the scope of use clauses.

-- 
                                           Robert I. Eachus

100% Ada, no bugs--the only way to create software.




^ permalink raw reply	[relevance 5%]

* Re: Clause "with and use"
  @ 2003-11-15 16:15  4%                       ` Gautier Write-only
  2003-11-16  0:02  5%                         ` Robert I. Eachus
  0 siblings, 1 reply; 132+ results
From: Gautier Write-only @ 2003-11-15 16:15 UTC (permalink / raw)


Robert I. Eachus:

> Bzzzt! Wrong Answer, try again.  A use clasue in Ada does NOT imply that
> there is a with around somewhere.  Try compiling:
> 
> procedure Junk is
>    use Ascii;
> begin null; end Junk;
> 
> If you have any doubts about that.
> 
> Ascii is somewhat special, but fairly common is:
> 
> package Outer is...
>     package Inner is...
> 
> end Outer;
> 
> package body Outer is
>    use Inner;
>    ...
> end Outer;
> 
> Again a use clause without a with clause in sight.

Both "use" you cite are not context clauses -> OT, sorry !

BTW, your mention of ASCII is interesting.
* Ada 83 (and later) implies a non-written "with Standard; use Standard;"
  - ASCII is subpackage of Standard.
* Ada 95 (and later) implies a non-written "with Ada, Ada.Strings;" when you
  just write "with Ada.Strings.Maps;". Same for all children 

-> things are not at all 100% explicit in the present standard.

* The "[with and ]use" proposal offers the possibility of writing once
  the name of a package instead of twice when you use "use" in a context clause.

-> this feature doesn't reduce from 1 to 0 the appearance of a package name
   like both mentioned above, but from 2 to 1. When the feature is used, the
   names remain explicit, but without redundance.

Clearly the contestation about this proposal is just because this is an evolution.
Existing elements are by default sacred, improvements are by default suscpicious...
________________________________________________________
Gautier  --  http://www.mysunrise.ch/users/gdm/gsoft.htm

NB: For a direct answer, e-mail address on the Web site!



^ permalink raw reply	[relevance 4%]

* Re: conversion
  @ 2003-06-27 18:42  6% ` tmoran
  0 siblings, 0 replies; 132+ results
From: tmoran @ 2003-06-27 18:42 UTC (permalink / raw)


>Hmmm.  Where to begin.  You are thinking in C about Ada concepts.  That
>is confusing you because the Ada mappings are different.  In Ada, the
  As a general rule, if something seems inordinately hard to do in Ada,
you are probably not using Ada appropriately.  In the case of strings,
declaring dynamically sized strings, passing strings as dynamically sized
parameters, using concatenation, and, especially, using slices will handle
a great many string processing tasks.  eg,

  procedure Process_Line(Line : in String) is
  -- From "Fred Smith #12345; John Jones, Albert"
  -- make 2 calls on Process_First_Name
  --   Process_Full_Name("Smith, Fred");
  --   Process_Full_Name("Jones, John");
    First, Last : Natural;
  begin
    First := Line'first;
    loop
      Ada.Strings.Fixed.Find_Token
           (Source=>Line(First .. Line'last),
            Set   =>Ada.Strings.Maps.Constants.Letter_Set,
            Test  =>Ada.Strings.Inside,
            First =>First,
            Last  =>Last);
      exit when Last = 0;
      declare
        use Ada.Strings;
        use Ada.Strings.Maps.Constants;
        First_Name : String renames Line(First .. Last);
      begin
        Fixed.Find_Token(Line(Last+1 .. Line'last), Letter_Set, Inside,
                         First, Last);
        exit when Last = 0;
        Process_Full_Name(Line(First .. Last) & ", " & First_Name);
      end;
      First := Last+1;
    end loop;
  end Process_Line;
  ...
  Line : String(1 .. 80);
  Last : Natural;
  ...
  Ada.Text_IO.Get_Line(Input, Line, Last);
  Process_Line(Line(Line'first .. Last));



^ permalink raw reply	[relevance 6%]

* Re: Visibility
       [not found]     <009C830A.36D4A463.0015D3EC@netscape.net>
@ 2003-06-07 12:18  0% ` David C. Hoos, Sr.
  0 siblings, 0 replies; 132+ results
From: David C. Hoos, Sr. @ 2003-06-07 12:18 UTC (permalink / raw)
  To: And838N, comp.lang.ada


----- Original Message ----- 
From: <And838N@netscape.net>
To: <comp.lang.ada@ada.eu.org>
Sent: June 07, 2003 3:21 AM
Subject: Visibility


> >Why did you "with" and "use" ada.text_io, when your program doesn't 
> >need them?  Elimination of this error solves the problem of visibility 
> >of "count". 
> Well, if I don't "with" ada.text_io I get the following message from
> gnatmake.
> iotest.adb:4:09: "put_line" is undefined
> iotest.adb:4:09: possible missing with of Text_IO
> iotest.adb:4:10: "put" is undefined
> iotest.adb:4:10: possible missing with of Text_IO
> hence, the reason I "withed" text_io.
> 
If you look at your original post (on June 4), there was no "put_line"
statement -- hence, the reason for my question 
> >I could find no such statement on my copy of Cohen's book. 
> Page 1039, Section A.2
> 
> >There is no such unit as "unbounded_text_io" in the Ada standard
> >libraries. 
> Hmmm...I have a "with" for Ada.strings.unbounded.text_io and the file 
> in <libdirectory>/adainclude/a-suteio.ads (using gcc-lib) says
> otherwise.  The package that has the Count function I am talking about
> is ada.strings.unbounded.
> 
> According to Cohen and obviously GNAT, the Count variable in text_io
> and the function with the same name from unbounded are visible in the
> same place, and for some reason it, GNAT, does not "determine" or maybe
> cannot determine which one to use by "signature".  To me, if anything,
> GNAT should have said something to the effect that I was trying to
> perform some sort of narrowing conversion rather than telling me that
> it did not know which Count to use because of a visibility issue.

First, Ada.Text_IO.Count is a _type_, not a variable as you state above.
Secondly, GNAT did _not_ tell you it didn't know which one to use.  It
told you (clearly and correctly) that multiple "use" clauses cause hiding,
which is correct according to the visibility rules. 
> 
> with
> ada.strings.unbounded,
> ada.text_io,
> ada.strings.maps;
> 
> use
> ada.strings.unbounded,
> ada.text_io,
> ada.strings.maps;
> 
> procedure visibilitytest is
>         astring: string := "hello world";
>         somenumber: integer;
> begin
>         put_line(astring);
>         somenumber := count(to_unbounded_string(astring), to_set(' '));
>         put_line(Integer'image(somenumber));
> end visibilitytest;
> 
> This code does not compile first because of a visibility issue.  The
> compiler output, gnatmake visibilitytest.adb -gnatf, yields:
> adagcc -c -gnatf visibilitytest.adb
> visibilitytest.adb:18:23: "count" is not visible
> visibilitytest.adb:18:23: multiple use clauses cause hiding
> visibilitytest.adb:18:23: hidden declaration at a-textio.ads:66
> visibilitytest.adb:18:23: hidden declaration at a-strunb.ads:217
> visibilitytest.adb:18:23: hidden declaration at a-strunb.ads:211
> visibilitytest.adb:18:23: hidden declaration at a-strunb.ads:205
> gnatmake: "visibilitytest.adb" compilation error
> 
> The fix is to specify which one to use on line 18.
> somenumber := ada.strings.unbounded.count(to_unbounded_string(as
> tring), to_set(' '));.  To me, GNAT should be able to resolve which
> count to use because the count in ada.strings.unbounded is a function
> and count in ada.text_io is a type.  Not to mention the function
> returns (or is of type) Natural, not count.
> 
> The answer to my question was in Cohen's book, chapter 10.  The 
> rules for the "with" clause and packages are to make a large 
> number of files easier to manage and to make it clear to the reader
> what is going on with any particular file.  The "with" clause just
> makes "stuff" visible; it is up to the programmer/engineer to specify
> or clarify, by using an expanded name, what facilities they are "use"
> ing from a particular package.  Thus, GNAT's compiler message tells
> me not that GNAT can't determine which count to use but that I need
> to specify, for future readers, which count I needed.  In doing so
> ,if I am searching for count, I narrow the search to the exact 
> package I need to look in for the count I "used". 
> 
> I'll be looking into Elaboration next.  It sounds to me like the 
> elaboration of a package is like the instantiation of a C++ class.
> If that's true, then I should be able to have multiple elaborations
> of a package that all have different values for their data members.
> And if that is true, then I've been using the package the wrong way.

Elaboration is nothing at all like the instantiation of a C++ class.
Elaboration is a _process_ that takes place at program startup wherein
declarations are executed -- e.g. to initialize a constant or variable.

Suppose you had the following declarations in the specification of a
package named my_pkg:

angle : Long_Float := 13.0;
base : Long_Float := 1234.5;
package Long_Float_Elementary_Functions is new
   Ada.Numerics.Generic_Elementary_Functions (Long_Float);
use Long_Float_Elementary_Functions;
altitude : Long_Float := base * Sin (angle * Ada.Numerics.Pi / 180.0);

Using the GNAT compiler, the object file resulting from the compilation
of your package would contain a procedure named my_pkg___elabs.

That procedure contains the elaboration code for your package
specification.

When compiling your main program, the compiler will insert code to
call that elaboration procedure as well as the elaboration procedures
of all of the compilation units making up your program.

_That's_ what elaboration is.

> 
> Thanks for the help all.
> 
> Andrew
> 
> __________________________________________________________________
> McAfee VirusScan Online from the Netscape Network.
> Comprehensive protection for your entire computer. Get your free trial today!
> http://channels.netscape.com/ns/computing/mcafee/index.jsp?promo=393397
> 
> Get AOL Instant Messenger 5.1 free of charge.  Download Now!
> http://aim.aol.com/aimnew/Aim/register.adp?promo=380455
> _______________________________________________
> comp.lang.ada mailing list
> comp.lang.ada@ada.eu.org
> http://ada.eu.org/mailman/listinfo/comp.lang.ada
> 
> 




^ permalink raw reply	[relevance 0%]

* Visibility
@ 2003-06-07  8:21  5% And838N
  0 siblings, 0 replies; 132+ results
From: And838N @ 2003-06-07  8:21 UTC (permalink / raw)
  To: comp.lang.ada

>Why did you "with" and "use" ada.text_io, when your program doesn't 
>need them?  Elimination of this error solves the problem of visibility 
>of "count". 
Well, if I don't "with" ada.text_io I get the following message from
gnatmake.
iotest.adb:4:09: "put_line" is undefined
iotest.adb:4:09: possible missing with of Text_IO
iotest.adb:4:10: "put" is undefined
iotest.adb:4:10: possible missing with of Text_IO
hence, the reason I "withed" text_io.
 
>I could find no such statement on my copy of Cohen's book. 
Page 1039, Section A.2

>There is no such unit as "unbounded_text_io" in the Ada standard
>libraries. 
Hmmm...I have a "with" for Ada.strings.unbounded.text_io and the file 
in <libdirectory>/adainclude/a-suteio.ads (using gcc-lib) says
otherwise.  The package that has the Count function I am talking about
is ada.strings.unbounded.

According to Cohen and obviously GNAT, the Count variable in text_io
and the function with the same name from unbounded are visible in the
same place, and for some reason it, GNAT, does not "determine" or maybe
cannot determine which one to use by "signature".  To me, if anything,
GNAT should have said something to the effect that I was trying to
perform some sort of narrowing conversion rather than telling me that
it did not know which Count to use because of a visibility issue.

with
ada.strings.unbounded,
ada.text_io,
ada.strings.maps;

use
ada.strings.unbounded,
ada.text_io,
ada.strings.maps;

procedure visibilitytest is
        astring: string := "hello world";
        somenumber: integer;
begin
        put_line(astring);
        somenumber := count(to_unbounded_string(astring), to_set(' '));
        put_line(Integer'image(somenumber));
end visibilitytest;

This code does not compile first because of a visibility issue.  The
compiler output, gnatmake visibilitytest.adb -gnatf, yields:
adagcc -c -gnatf visibilitytest.adb
visibilitytest.adb:18:23: "count" is not visible
visibilitytest.adb:18:23: multiple use clauses cause hiding
visibilitytest.adb:18:23: hidden declaration at a-textio.ads:66
visibilitytest.adb:18:23: hidden declaration at a-strunb.ads:217
visibilitytest.adb:18:23: hidden declaration at a-strunb.ads:211
visibilitytest.adb:18:23: hidden declaration at a-strunb.ads:205
gnatmake: "visibilitytest.adb" compilation error

The fix is to specify which one to use on line 18.
somenumber := ada.strings.unbounded.count(to_unbounded_string(as
tring), to_set(' '));.  To me, GNAT should be able to resolve which
count to use because the count in ada.strings.unbounded is a function
and count in ada.text_io is a type.  Not to mention the function
returns (or is of type) Natural, not count.

The answer to my question was in Cohen's book, chapter 10.  The 
rules for the "with" clause and packages are to make a large 
number of files easier to manage and to make it clear to the reader
what is going on with any particular file.  The "with" clause just
makes "stuff" visible; it is up to the programmer/engineer to specify
or clarify, by using an expanded name, what facilities they are "use"
ing from a particular package.  Thus, GNAT's compiler message tells
me not that GNAT can't determine which count to use but that I need
to specify, for future readers, which count I needed.  In doing so
,if I am searching for count, I narrow the search to the exact 
package I need to look in for the count I "used". 

I'll be looking into Elaboration next.  It sounds to me like the 
elaboration of a package is like the instantiation of a C++ class.
If that's true, then I should be able to have multiple elaborations
of a package that all have different values for their data members.
And if that is true, then I've been using the package the wrong way.

Thanks for the help all.

Andrew

__________________________________________________________________
McAfee VirusScan Online from the Netscape Network.
Comprehensive protection for your entire computer. Get your free trial today!
http://channels.netscape.com/ns/computing/mcafee/index.jsp?promo=393397

Get AOL Instant Messenger 5.1 free of charge.  Download Now!
http://aim.aol.com/aimnew/Aim/register.adp?promo=380455



^ permalink raw reply	[relevance 5%]

* Re: visibility
       [not found]     <666191F6.00B406DF.0015D3EC@netscape.net>
@ 2003-06-05 15:16  3% ` David C. Hoos
  0 siblings, 0 replies; 132+ results
From: David C. Hoos @ 2003-06-05 15:16 UTC (permalink / raw)
  To: And838N, comp.lang.ada


----- Original Message ----- 
From: <And838N@netscape.net>
To: <comp.lang.ada@ada.eu.org>
Sent: Wednesday, June 04, 2003 5:12 PM
Subject: visibility


> Ok, here's another question.  I'll provide some background information
first.
>
> Let us say that there is a procedure in an .adb file that is not in a
> package and it looks something like the following:
>
> ----------------------
> with
> ada.text_io,
> ada.integer_text_io,
> ada.strings.unbounded;
>
> use
> ada.text_io,
> ada.integer_text_io,
> ada.strings.unbounded;
>
> procedure x is
>     astring: unbounded_string := "hello world";
>     somenumber: integer := 0;
> begin
>     somenumber := count(astring, to_set(' '));
>     put(somenumber);
> end x;
> -----------------------
>
> Now we go compile it and GNAT gives me a message that says there is
> more than one "count" and that I have to specify, by using the full
> package name before the word count, in order to specify which count I
> want.  Which isn't so bad, yet...

First of all, gnat dows not report what you said it reports; here's the
actual report:
x.adb:12:34: expected private type "Ada.Strings.Unbounded.Unbounded_String"
x.adb:12:34: found a string type
x.adb:15:19: "count" is not visible
x.adb:15:19: multiple use clauses cause hiding
x.adb:15:19: hidden declaration at a-strunb.ads:217
x.adb:15:19: hidden declaration at a-strunb.ads:211
x.adb:15:19: hidden declaration at a-strunb.ads:205
x.adb:15:19: hidden declaration at a-textio.ads:66
x.adb:15:34: "to_set" is not visible
x.adb:15:34: non-visible declaration at a-strmap.ads:107
x.adb:15:34: non-visible declaration at a-strmap.ads:105
x.adb:15:34: non-visible declaration at a-strmap.ads:70
x.adb:15:34: non-visible declaration at a-strmap.ads:68

As is usual, the gnat error messages are very clear and precise.  You
need to eliminate the errors in order.  Changing the declaration of
"astring" to a correct one soves that problem.  E.g. change it to:

astring: Unbounded_String := To_Unbounded_String ("hello world");

Ada does not do implicit conversions -- i.e. it does not "automagically"
do things behind the scenes that might not be what you intended.

The second error -- the invisibility of "count" is discussed below.

The third error -- the invisibility of "to_set" is corrected by including
"ada.strings.maps" in your "with" and "use" clauses.
>
> So out of curiosity I look at the version of count inside ada.text_io
> and compare it to the version of count inside ada.strings.unbounded.
> Turns out the count inside ada.text_io isn't a "procedure" at all, it's
> a variable type.

Why did you "with" and "use" ada.text_io, when your program doesn't
need them?  Elimination of this error solves the problem of visibility
of "count".

>
> So I investigate further.  The author of Ada as a second language,
> Norman Cohen provided a chapter on scope and visiblity.  In that
> chapter (actually an appendix), he says that one of the only times
> there will be a visibility problem is when a variable type and a
> procedure have the same name.

I could find no such statement on my copy of Cohen's book.

He does say that "hiding" should be avoided, so you should have heeded the
compiler message.

>
> It is hard for me to accept that Ada (GNAT) can't tell the difference
> between a variable type and a procedure?  I wouldn't be surprised if
> both counts were procedures or both counts were variable types, having the
same "signature".  But a variable type compared to a procedure?
The "count" you are using in your program is not a procedure; it's a
function.
The "count" in Ada.Text_IO is a type (there's no such thing as a "variable
type" in Ada.
Ada types can be used to declare constants as well as variables.

When a type name appears after ":=" -- i.e., in an expression -- the
compiler would
think it was a type conversion.  Type conversions have the same syntax as a
function call.

> Does that mean that after a visibility conflict occurs when compiling
> that there is no "signature" checking? Can someone please explain?
>
> Second question related to "with"ing and "use"ing. (I think the first
> question might be resolved by re-working my "with"s and "use"s.)
> If I "with" ada.strings, that makes it, and it's children "visible" to
> my procedure or package?

No. The children are not visible. You must explicitly "with" the children
you will use.

> If so, then I can "use" only the children I want, like fixed,
> unbounded, unbounded_text_io, etcetera?

There is no such unit as "unbounded_text_io" in the Ada standard libraries.

> If so, does the compiler or linker still link in, or for lack of a
> better term "insert" code into my procedure/package for the children I
> didn't "use"?

"Use" clauses affect only visibility; they have no effect on linking.
All compilation units "withed" are linked into the executable, regardless of
whether
they are referenced in your program.
>
> Thanks,
>
> Andrew
>
> P.S.
> How's the word wrap now?
>
>
>
> __________________________________________________________________
> McAfee VirusScan Online from the Netscape Network.
> Comprehensive protection for your entire computer. Get your free trial
today!
> http://channels.netscape.com/ns/computing/mcafee/index.jsp?promo=393397
>
> Get AOL Instant Messenger 5.1 free of charge.  Download Now!
> http://aim.aol.com/aimnew/Aim/register.adp?promo=380455
> _______________________________________________
> comp.lang.ada mailing list
> comp.lang.ada@ada.eu.org
> http://ada.eu.org/mailman/listinfo/comp.lang.ada
>




^ permalink raw reply	[relevance 3%]

* Re: Base 12 Integer IO
       [not found]     <mailman.12.1044286941.3911.comp.lang.ada@ada.eu.org>
@ 2003-02-04  3:37  5% ` Steve
  0 siblings, 0 replies; 132+ results
From: Steve @ 2003-02-04  3:37 UTC (permalink / raw)



"Paolo Argenton" <paoloa1@yahoo.com> wrote in message
news:mailman.12.1044286941.3911.comp.lang.ada@ada.eu.org...
Hi all !
I would like to do base 12 Integer IO;
while the following code fragment works
   for I in 0..1488 loop
      Put( I, Width => 3, Base => 12 );

It has 2 drawbacks (for me at least)
1) the output is with leading base number and # i.e. 12#A40# while I would
like to have the raw A40, for instance.
2) width is not fixed, i.e. I would like to have in the output 005 for -say-
number 5 instead of one digit only.
How can I fix these things? Can I do Integer IO to a string, in order to
reformat the string as I desire?
Thanks everybody
Paolo

Here is a small example (that runs and produces the correct result):

WITH Ada.Strings.Fixed;
 USE Ada.Strings.Fixed;
WITH Ada.Strings.Maps;
 USE Ada.Strings.Maps;
WITH Ada.Text_Io;
 USE Ada.Text_Io;
WITH Ada.Integer_Text_Io;
 USE Ada.Integer_Text_Io;
PROCEDURE GetNumString IS

  value : Integer := 42;
  buffer : String( 1 .. 32 );
BEGIN
  Put( buffer, value, 12 );
  DECLARE
    lbSet : Character_Set := To_Set( '#' );
    notLb : Character_Set := NOT lbSet;
    text : String := Tail( Trim( Trim( buffer, notLb, notLb ),
                                 lbSet, lbSet), 4, '0' );
  BEGIN
    Put_Line( text );
  END;
END GetNumString;


Yahoo! Cellulari: loghi, suonerie, picture message per il tuo telefonino





^ permalink raw reply	[relevance 5%]

* RE: Character Sets (plain text police report)
  @ 2002-11-29 20:37  3% ` Robert C. Leif
  0 siblings, 0 replies; 132+ results
From: Robert C. Leif @ 2002-11-29 20:37 UTC (permalink / raw)


Oops. My apologies.
Bob Leif
The correct text version is below. 
Addendum: The solution is the creation of versions of Ada.Strings.Bounded for 16 and 32 bit characters. The 32 bit Unicode characters allow direct comparison of characters based on their position in Unicode.

-----Original Message-----
From: comp.lang.ada-admin@ada.eu.org [mailto:comp.lang.ada-admin@ada.eu.org] On Behalf Of Warren W. Gay VE3WWG
Sent: Thursday, November 28, 2002 10:09 AM
To: comp.lang.ada@ada.eu.org
Subject: Re: Character Sets (plain text police report)

Hmmm... I guess since Robert Dewar is avoiding this group these
days, we also lost our "plain text" police force ;-)

In case you were not aware of it, you are posting HTML to this
news group. This is generally discouraged so that others who
are not using HTML capable news readers, are still able to make
sense of your posting.
--------------------------------------------------------
Christoph Grein responded to my inquiry by stating that,
" Latin_9.Euro_Sign is a name for a character. The same character in Latin_1 has a different name, it is the Currency_Sign." "So why do you expect this character not to be in the set only because you use a different name for it?" The Euro_Sign and the Currency_Sign have a different representation according to The ISO 8859 Alphabet Soup http://czyborra.com/charsets/iso8859.html
------------------------------------------------
GNAT Latin_9 (ISO-8859-15)includes the following:
   -- Summary of Changes from Latin-1 => Latin-9 --
   ------------------------------------------------

   --   164     Currency                => Euro_Sign
   --   166     Broken_Bar              => UC_S_Caron
   --   168     Diaeresis               => LC_S_Caron
   --   180     Acute                   => UC_Z_Caron
   --   184     Cedilla                 => LC_Z_Caron
   --   188     Fraction_One_Quarter    => UC_Ligature_OE
   --   189     Fraction_One_Half       => LC_Ligature_OE
   --   190     Fraction_Three_Quarters => UC_Y_Diaeresis
Since these are changes, they should not be the same character. Below are the results of an extension of my original program that now tests the characters of Latin_9 from character number 164 through 190 and prints them out. I understand that choice of the Windows font will change their representation. The correct glyphs can be found at The ISO 8859 Alphabet Soup. For anyone interested, I have put my program at the end of this note. I suspect that the best solution would be to introduce UniCode, ISO/IEC 10646, into the Ada standard. The arguments for this are contained in W3C Character Model for the World Wide Web 1.0, W3C Working Draft 30 April 2002 http://www.w3.org/TR/charmod/ "The choice of Unicode was motivated by the fact that Unicode: is the only universal character repertoire available, covers the widest possible range, provides a way of referencing characters independent of the encoding of a resource, is being updated/completed carefully, is widely accepted and implemented by industry." "W3C adopted Unicode as the document character set for HTML in [HTML 4.0]. The same approach was later used for specifications such as XML 1.0 [XML 1.0] and CSS2 [CSS2]. Unicode now serves as a common reference for W3C specifications and applications." "The IETF has adopted some policies on the use of character sets on the Internet (see [RFC 2277])." Bob Leif ------------------------Starting Test----------------------- Latin_9_Diff is ñѪº¿⌐¬½¼¡«»░▒▓│┤╡╢╖╕╣║╗╝╜╛

The Character ñ is in Latin_1 is TRUE. Its position is  164
The Character Ñ is in Latin_1 is TRUE. Its position is  165
The Character ª is in Latin_1 is TRUE. Its position is  166
The Character º is in Latin_1 is TRUE. Its position is  167
The Character ¿ is in Latin_1 is TRUE. Its position is  168
The Character ⌐ is in Latin_1 is TRUE. Its position is  169
The Character ¬ is in Latin_1 is TRUE. Its position is  170
The Character ½ is in Latin_1 is TRUE. Its position is  171
The Character ¼ is in Latin_1 is TRUE. Its position is  172
The Character ¡ is in Latin_1 is TRUE. Its position is  173
The Character « is in Latin_1 is TRUE. Its position is  174
The Character » is in Latin_1 is TRUE. Its position is  175
The Character ░ is in Latin_1 is TRUE. Its position is  176
The Character ▒ is in Latin_1 is TRUE. Its position is  177
The Character ▓ is in Latin_1 is TRUE. Its position is  178
The Character │ is in Latin_1 is TRUE. Its position is  179
The Character ┤ is in Latin_1 is TRUE. Its position is  180
The Character ╡ is in Latin_1 is TRUE. Its position is  181
The Character ╢ is in Latin_1 is TRUE. Its position is  182
The Character ╖ is in Latin_1 is TRUE. Its position is  183
The Character ╕ is in Latin_1 is TRUE. Its position is  184
The Character ╣ is in Latin_1 is TRUE. Its position is  185
The Character ║ is in Latin_1 is TRUE. Its position is  186
The Character ╗ is in Latin_1 is TRUE. Its position is  187
The Character ╝ is in Latin_1 is TRUE. Its position is  188
The Character ╜ is in Latin_1 is TRUE. Its position is  189
The Character ╛ is in Latin_1 is TRUE. Its position is  190 ------------------------Ending Test----------------------- --Robert C. Leif, Ph.D & Ada_Med Copyright all rights reserved. --Main Procedure 
--Created 27 November 2002
with Ada.Text_Io;
with Ada.Io_Exceptions;
with Ada.Exceptions;
with Ada.Strings;
with Ada.Strings.Maps;
with  Ada.Characters.Latin_1;
with  Ada.Characters.Latin_9;
procedure Char_Sets_Test is 
   ------------------Table of Contents------------- 
   package T_Io renames Ada.Text_Io;
   package Str_Maps renames Ada.Strings.Maps;
   package Latin_1 renames Ada.Characters.Latin_1;
   package Latin_9 renames Ada.Characters.Latin_9;
   subtype Character_Set_Type is Str_Maps.Character_Set;
   subtype Character_Sequence_Type is Str_Maps.Character_Sequence;

   -----------------End Table of Contents-------------
   Latin_1_Range    : constant Str_Maps.Character_Range
      := (Low => Latin_1.Nul, High => Latin_1.Lc_Y_Diaeresis);  
   Latin_1_Char_Set :          Character_Set_Type      
      := Str_Maps.To_Set (Span => Latin_1_Range);  
   --Standard for Ada '95
   -- Latin_9 Differences: Euro_Sign, Uc_S_Caron, Lc_S_Caron, Uc_Z_Caron, 
   -- Lc_Z_Caron, Uc_Ligature_Oe, Lc_Ligature_Oe, Uc_Y_Diaeresis.
   Latin_9_Diff_Latin_1_Super_Range  : constant Str_Maps.Character_Range
      := (Low => Latin_9.Euro_Sign, High => Latin_9.Uc_Y_Diaeresis);  
   Latin_9_Diff_Latin_1_Super_Set    :          Character_Set_Type      
      := Str_Maps.To_Set (Span => Latin_9_Diff_Latin_1_Super_Range);  
   Latin_9_Diff_Latin_1_Super_String :          Character_Sequence_Type 
      := Str_Maps.To_Sequence (Latin_9_Diff_Latin_1_Super_Set);  
   Character_Set_Name                :          String                 
      := "Latin_1";  
   ---------------------------------------------   
   procedure Test_Character_Sets (
         Character_Sequence_Var : in     Character_Sequence_Type; 
         Set                    : in     Character_Set_Type       ) is 
      Is_In_Character_Set : Boolean   := False;  
      Char                : Character := 'X';  
      Character_Set_Position : Positive := 164; -- Euro_Sign   
   begin--Test_Character_Sets
      T_Io.Put_Line("Latin_9_Diff is " & Latin_9_Diff_Latin_1_Super_String);
      T_Io.Put_Line("");
      Test_Chars:
         for I in Character_Sequence_Var'range loop
         Char:= Character_Sequence_Var(I);
         Is_In_Character_Set:= Str_Maps.Is_In(
            Element => Char,            
            Set     => Latin_1_Char_Set);
         T_Io.Put_Line("The Character " & Char & " is in " & Character_Set_Name
            &  " is " & Boolean'Image (
               Is_In_Character_Set) & ". Its position is "
                  & Positive'Image(Character_Set_Position));
         Character_Set_Position:= Character_Set_Position + 1;
      end loop Test_Chars;
   end Test_Character_Sets;
   ---------------------------------------------     
begin--Bd_W_Char_Sets_Test
   T_Io.Put_Line("----------------------Starting Test---------------------);
   Test_Character_Sets (
      Character_Sequence_Var => Latin_9_Diff_Latin_1_Super_String, 
      Set                    => Latin_1_Char_Set);
   ---------------------------------------------
   T_Io.Put_Line("------------------------Ending Test---------------------);

exception
   when A: Ada.Io_Exceptions.Status_Error =>
      T_Io.Put_Line("Status_Error in Char_Sets_Test.");
      T_Io.Put_Line(Ada.Exceptions.Exception_Information(A));
   when O: others =>
      T_Io.Put_Line("Others_Error in Char_Sets_Test.");
      T_Io.Put_Line(Ada.Exceptions.Exception_Information(O));

end Char_Sets_Test;




^ permalink raw reply	[relevance 3%]

* Re: Character Sets
@ 2002-11-28 17:53  3% Robert C. Leif
  0 siblings, 0 replies; 132+ results
From: Robert C. Leif @ 2002-11-28 17:53 UTC (permalink / raw)


Christoph Grein responded to my inquiry by stating that,
" Latin_9.Euro_Sign is a name for a character. The same character in Latin_1 has a different name, it is the Currency_Sign."
"So why do you expect this character not to be in the set only because you use a different name for it?"
The Euro_Sign and the Currency_Sign have a different representation according to The ISO 8859 Alphabet Soup http://czyborra.com/charsets/iso8859.html
------------------------------------------------
GNAT Latin_9 (ISO-8859-15)includes the following:
   -- Summary of Changes from Latin-1 => Latin-9 --
   ------------------------------------------------

   --   164     Currency                => Euro_Sign
   --   166     Broken_Bar              => UC_S_Caron
   --   168     Diaeresis               => LC_S_Caron
   --   180     Acute                   => UC_Z_Caron
   --   184     Cedilla                 => LC_Z_Caron
   --   188     Fraction_One_Quarter    => UC_Ligature_OE
   --   189     Fraction_One_Half       => LC_Ligature_OE
   --   190     Fraction_Three_Quarters => UC_Y_Diaeresis
Since these are changes, they should not be the same character.
Below are the results of an extension of my original program that now tests the characters of Latin_9 from character number 164 through 190 and prints them out. I understand that choice of the Windows font will change their representation. The correct glyphs can be found at The ISO 8859 Alphabet Soup. For anyone interested, I have put my program at the end of this note.
I suspect that the best solution would be to introduce UniCode, ISO/IEC 10646, into the Ada standard. The arguments for this are contained in W3C Character Model for the World Wide Web 1.0, W3C Working Draft 30 April 2002
http://www.w3.org/TR/charmod/
"The choice of Unicode was motivated by the fact that Unicode: is the only universal character repertoire available, covers the widest possible range, provides a way of referencing characters independent of the encoding of a resource, is being updated/completed carefully, is widely accepted and implemented by industry."
"W3C adopted Unicode as the document character set for HTML in [HTML 4.0]. The same approach was later used for specifications such as XML 1.0 [XML 1.0] and CSS2 [CSS2]. Unicode now serves as a common reference for W3C specifications and applications."
"The IETF has adopted some policies on the use of character sets on the Internet (see [RFC 2277])."
Bob Leif
------------------------Starting Test-----------------------
Latin_9_Diff is ñѪº¿⌐¬½¼¡«»░▒▓│┤╡╢╖╕╣║╗╝╜╛

The Character ñ is in Latin_1 is TRUE. Its position is  164
The Character Ñ is in Latin_1 is TRUE. Its position is  165
The Character ª is in Latin_1 is TRUE. Its position is  166
The Character º is in Latin_1 is TRUE. Its position is  167
The Character ¿ is in Latin_1 is TRUE. Its position is  168
The Character ⌐ is in Latin_1 is TRUE. Its position is  169
The Character ¬ is in Latin_1 is TRUE. Its position is  170
The Character ½ is in Latin_1 is TRUE. Its position is  171
The Character ¼ is in Latin_1 is TRUE. Its position is  172
The Character ¡ is in Latin_1 is TRUE. Its position is  173
The Character « is in Latin_1 is TRUE. Its position is  174
The Character » is in Latin_1 is TRUE. Its position is  175
The Character ░ is in Latin_1 is TRUE. Its position is  176
The Character ▒ is in Latin_1 is TRUE. Its position is  177
The Character ▓ is in Latin_1 is TRUE. Its position is  178
The Character │ is in Latin_1 is TRUE. Its position is  179
The Character ┤ is in Latin_1 is TRUE. Its position is  180
The Character ╡ is in Latin_1 is TRUE. Its position is  181
The Character ╢ is in Latin_1 is TRUE. Its position is  182
The Character ╖ is in Latin_1 is TRUE. Its position is  183
The Character ╕ is in Latin_1 is TRUE. Its position is  184
The Character ╣ is in Latin_1 is TRUE. Its position is  185
The Character ║ is in Latin_1 is TRUE. Its position is  186
The Character ╗ is in Latin_1 is TRUE. Its position is  187
The Character ╝ is in Latin_1 is TRUE. Its position is  188
The Character ╜ is in Latin_1 is TRUE. Its position is  189
The Character ╛ is in Latin_1 is TRUE. Its position is  190
------------------------Ending Test-----------------------
--Robert C. Leif, Ph.D & Ada_Med Copyright all rights reserved.
--Main Procedure 
--Created 27 November 2002
with Ada.Text_Io;
with Ada.Io_Exceptions;
with Ada.Exceptions;
with Ada.Strings;
with Ada.Strings.Maps;
with  Ada.Characters.Latin_1;
with  Ada.Characters.Latin_9;
procedure Char_Sets_Test is 
   ------------------Table of Contents------------- 
   package T_Io renames Ada.Text_Io;
   package Str_Maps renames Ada.Strings.Maps;
   package Latin_1 renames Ada.Characters.Latin_1;
   package Latin_9 renames Ada.Characters.Latin_9;
   subtype Character_Set_Type is Str_Maps.Character_Set;
   subtype Character_Sequence_Type is Str_Maps.Character_Sequence;

   -----------------End Table of Contents-------------
   Latin_1_Range    : constant Str_Maps.Character_Range
      := (Low => Latin_1.Nul, High => Latin_1.Lc_Y_Diaeresis);  
   Latin_1_Char_Set :          Character_Set_Type      
      := Str_Maps.To_Set (Span => Latin_1_Range);  
   --Standard for Ada '95
   -- Latin_9 Differences: Euro_Sign, Uc_S_Caron, Lc_S_Caron, Uc_Z_Caron, 
   -- Lc_Z_Caron, Uc_Ligature_Oe, Lc_Ligature_Oe, Uc_Y_Diaeresis.
   Latin_9_Diff_Latin_1_Super_Range  : constant Str_Maps.Character_Range
      := (Low => Latin_9.Euro_Sign, High => Latin_9.Uc_Y_Diaeresis);  
   Latin_9_Diff_Latin_1_Super_Set    :          Character_Set_Type      
      := Str_Maps.To_Set (Span => Latin_9_Diff_Latin_1_Super_Range);  
   Latin_9_Diff_Latin_1_Super_String :          Character_Sequence_Type 
      := Str_Maps.To_Sequence (Latin_9_Diff_Latin_1_Super_Set);  
   Character_Set_Name                :          String                 
      := "Latin_1";  
   ---------------------------------------------   
   procedure Test_Character_Sets (
         Character_Sequence_Var : in     Character_Sequence_Type; 
         Set                    : in     Character_Set_Type       ) is 
      Is_In_Character_Set : Boolean   := False;  
      Char                : Character := 'X';  
      Character_Set_Position : Positive := 164; -- Euro_Sign   
   begin--Test_Character_Sets
      T_Io.Put_Line("Latin_9_Diff is " & Latin_9_Diff_Latin_1_Super_String);
      T_Io.Put_Line("");
      Test_Chars:
         for I in Character_Sequence_Var'range loop
         Char:= Character_Sequence_Var(I);
         Is_In_Character_Set:= Str_Maps.Is_In(
            Element => Char,            
            Set     => Latin_1_Char_Set);
         T_Io.Put_Line("The Character " & Char & " is in " & Character_Set_Name
            &  " is " & Boolean'Image (
               Is_In_Character_Set) & ". Its position is "
                  & Positive'Image(Character_Set_Position));
         Character_Set_Position:= Character_Set_Position + 1;
      end loop Test_Chars;
   end Test_Character_Sets;
   ---------------------------------------------     
begin--Bd_W_Char_Sets_Test
   T_Io.Put_Line("----------------------Starting Test---------------------);
   Test_Character_Sets (
      Character_Sequence_Var => Latin_9_Diff_Latin_1_Super_String, 
      Set                    => Latin_1_Char_Set);
   ---------------------------------------------
   T_Io.Put_Line("------------------------Ending Test---------------------);

exception
   when A: Ada.Io_Exceptions.Status_Error =>
      T_Io.Put_Line("Status_Error in Char_Sets_Test.");
      T_Io.Put_Line(Ada.Exceptions.Exception_Information(A));
   when O: others =>
      T_Io.Put_Line("Others_Error in Char_Sets_Test.");
      T_Io.Put_Line(Ada.Exceptions.Exception_Information(O));

end Char_Sets_Test;




^ permalink raw reply	[relevance 3%]

* Re: Character Sets
@ 2002-11-27  9:00  0% Grein, Christoph
  0 siblings, 0 replies; 132+ results
From: Grein, Christoph @ 2002-11-27  9:00 UTC (permalink / raw)


> From: Bob Leif
> I am trying to test if a character is not in the Latin_1 character set.
> I choose the Euro because it is in Latin_9 and not in Latin_1. I tested
> the function Ada.Strings.Maps.Is_In. It returns that the Euro_Sign is in
> the Latin_1 character set. What have I done wrong?
> My test program, which compiled and executed under GNAT 3.15p under
> Windows XP, produced:
> ------------------------Starting Test-----------------------
> Is_In_Character_Set is TRUE
> ------------------------Ending Test-----------------------
>  The test program is as follows:
> ---------------------------------------------------------
> with Ada.Text_Io;
> with Ada.Io_Exceptions;
> with Ada.Exceptions;
> with Ada.Strings;
> with Ada.Strings.Maps;
> with  Ada.Characters.Latin_1;
> with  Ada.Characters.Latin_9;
> procedure Char_Sets_Test is 
>    ------------------Table of Contents------------- 
>    package T_Io renames Ada.Text_Io;
>    package Str_Maps renames Ada.Strings.Maps;
>    package Latin_1 renames Ada.Characters.Latin_1;
>    package Latin_9 renames Ada.Characters.Latin_9;
>    subtype Character_Set_Type is Str_Maps.Character_Set;
>    -----------------End Table of Contents-------------
>    Latin_1_Range    : constant Str_Maps.Character_Range
> 	 := (Low => Latin_1.Nul, High => Latin_1.Lc_Y_Diaeresis);  

This is the full range of type Character, isn't it.

>    Latin_1_Char_Set :          Character_Set_Type       :=
> Str_Maps.To_Set 	(Span => Latin_1_Range);  

So this is the set of all characters.

>    --Standard for Ada '95
>    Is_In_Character_Set : Boolean := False;  
>    ---------------------------------------------
> begin--Bd_W_Char_Sets_Test
>    T_Io.Put_Line("-----------------------Starting
> Test--------------------);
>    ---------------------------------------------
>    --Test Character_Sets
>    Is_In_Character_Set:=Ada.Strings.Maps.Is_In (
>       Element => Latin_9.Euro_Sign, 
>       Set     => Latin_1_Char_Set);

Latin_9.Euro_Sign is a name for a character. The same character in Latin1 has a 
different name, it is the Currency_Sign.

So why do you expect this character not to be in the set only because you use a 
different name for it?

>    T_Io.Put_Line("Is_In_Character_Set is " & Boolean'Image
> (Is_In_Character_Set));
>    ---------------------------------------------   
>    ---------------------------------------------
>    T_Io.Put_Line("-----------------------Ending
> Test----------------------);
> 
> exception
>    when A: Ada.Io_Exceptions.Status_Error =>
>       T_io.Put_Line("Status_Error in Char_Sets_Test.");
>       T_Io.Put_Line(Ada.Exceptions.Exception_Information(A));
>    when O: others =>
>       T_Io.Put_Line("Others_Error in Char_Sets_Test.");
>       T_Io.Put_Line(Ada.Exceptions.Exception_Information(O));
> end Char_Sets_Test;
> 
> _______________________________________________
> comp.lang.ada mailing list
> comp.lang.ada@ada.eu.org
> http://ada.eu.org/mailman/listinfo/comp.lang.ada



^ permalink raw reply	[relevance 0%]

* Character Sets
@ 2002-11-26 21:41  6% Robert C. Leif
  0 siblings, 0 replies; 132+ results
From: Robert C. Leif @ 2002-11-26 21:41 UTC (permalink / raw)


From: Bob Leif
I am trying to test if a character is not in the Latin_1 character set.
I choose the Euro because it is in Latin_9 and not in Latin_1. I tested
the function Ada.Strings.Maps.Is_In. It returns that the Euro_Sign is in
the Latin_1 character set. What have I done wrong?
My test program, which compiled and executed under GNAT 3.15p under
Windows XP, produced:
------------------------Starting Test-----------------------
Is_In_Character_Set is TRUE
------------------------Ending Test-----------------------
 The test program is as follows:
---------------------------------------------------------
with Ada.Text_Io;
with Ada.Io_Exceptions;
with Ada.Exceptions;
with Ada.Strings;
with Ada.Strings.Maps;
with  Ada.Characters.Latin_1;
with  Ada.Characters.Latin_9;
procedure Char_Sets_Test is 
   ------------------Table of Contents------------- 
   package T_Io renames Ada.Text_Io;
   package Str_Maps renames Ada.Strings.Maps;
   package Latin_1 renames Ada.Characters.Latin_1;
   package Latin_9 renames Ada.Characters.Latin_9;
   subtype Character_Set_Type is Str_Maps.Character_Set;
   -----------------End Table of Contents-------------
   Latin_1_Range    : constant Str_Maps.Character_Range
	 := (Low => Latin_1.Nul, High => Latin_1.Lc_Y_Diaeresis);  
   Latin_1_Char_Set :          Character_Set_Type       :=
Str_Maps.To_Set 	(Span => Latin_1_Range);  
   --Standard for Ada '95
   Is_In_Character_Set : Boolean := False;  
   ---------------------------------------------
begin--Bd_W_Char_Sets_Test
   T_Io.Put_Line("-----------------------Starting
Test--------------------);
   ---------------------------------------------
   --Test Character_Sets
   Is_In_Character_Set:=Ada.Strings.Maps.Is_In (
      Element => Latin_9.Euro_Sign, 
      Set     => Latin_1_Char_Set);
   T_Io.Put_Line("Is_In_Character_Set is " & Boolean'Image
(Is_In_Character_Set));
   ---------------------------------------------   
   ---------------------------------------------
   T_Io.Put_Line("-----------------------Ending
Test----------------------);

exception
   when A: Ada.Io_Exceptions.Status_Error =>
      T_io.Put_Line("Status_Error in Char_Sets_Test.");
      T_Io.Put_Line(Ada.Exceptions.Exception_Information(A));
   when O: others =>
      T_Io.Put_Line("Others_Error in Char_Sets_Test.");
      T_Io.Put_Line(Ada.Exceptions.Exception_Information(O));
end Char_Sets_Test;




^ permalink raw reply	[relevance 6%]

* Re: how to check if a string variable contains a number or string?
  @ 2002-11-19  3:19  6% ` SteveD
  0 siblings, 0 replies; 132+ results
From: SteveD @ 2002-11-19  3:19 UTC (permalink / raw)


"Sarah Thomas" <mabes180@aol.com> wrote in message
news:a04a773e.0211181241.4e9e13b0@posting.google.com...
> I have an array of strings that I read in from a file. I want to check
> if each element in the array is a string or if it is a number. is
> there any predefined functions that would help do that? thanks

There are some handy string handling functions in Ada.Strings.Fixed.

To do a quick check to see if a string contains an integer number I usually
create a map (Ada.Strings.Maps) and then search for a character that is
not a digit using Index (Ada.Strings.Fixed).  If I find a non-digit
character
it's not a number.

I just noticed that Ada.Strings.Maps defines a "Character_Sequence" as a
subtype string, and there is a Is_Subset function that could be used to do
the
job as well.

Of course this only works if the "numbers" are integers.

I hope this helps,
SteveD





^ permalink raw reply	[relevance 6%]

* Re: how to parse words from a string
  2002-11-14 13:40  5%         ` Sarah Thomas
@ 2002-11-14 14:56  6%           ` David C. Hoos
  0 siblings, 0 replies; 132+ results
From: David C. Hoos @ 2002-11-14 14:56 UTC (permalink / raw)



----- Original Message -----
From: "Sarah Thomas" <mabes180@aol.com>
Newsgroups: comp.lang.ada
To: <comp.lang.ada@ada.eu.org>
Sent: Thursday, November 14, 2002 7:40 AM
Subject: Re: how to parse words from a string


> Interesting follow ups! thanks for the input and help !
> I have succesfully extracted words from a string.
> I read each line in from the file
> and used find_token, followed by slice, followed by deleting the word
> from the string..and then stored them in a fixed array for now..
> this is just an outline of how i did it.....
>
> loop
> Find_Token(Temp, Ada.Strings.Maps.To_Set(Ada.Characters.Latin_1.HT),
> Ada.Strings.Outside, From, To);
> exit when To = 0;
>
> My_word := To_Unbounded_String(Slice(Temp, From, To));
> Put_line(Output_File,To_String(My_word));
>
> IF (Length(temp) /= To ) then
> Delete(Temp, 1, To + 1);
> else
> Delete(Temp, 1, To);
> end if;
>
> Store_data(Line_Number,Word_Number) := (My_Word);
>
> end loop;
You could have saved the work of repeatedly deleting from the
Temp string by initially setting To := Length (Temp) - 1;.

Then if you make your call to Find_Token like this:

Find_Token(Slice (Temp, To + 1, Length (Temp)),
Ada.Strings.Maps.To_Set(Ada.Characters.Latin_1.HT),
Ada.Strings.Outside, From, To);

you just specify the unprocessed slice of Temp each time you look for a new
token.

I'm sure you realize you could have declared a String of word delimiters to
include
spaces, punctuation marks and other white space characters in the set of
possible
word delimiters, and used that String to initialize a Word_Delimiter_Set --
e.g.:

Word_Delimiter_Set : constant Ada.Strings.Maps.Character_Set :=
Ada.Strings.Maps.To_Set
(" ,.;:/!&()" & Ada.Characters.Latin_1.HT & Ada.Characters.Latin_1.FF);






^ permalink raw reply	[relevance 6%]

* Re: how to parse words from a string
  @ 2002-11-14 13:40  5%         ` Sarah Thomas
  2002-11-14 14:56  6%           ` David C. Hoos
  0 siblings, 1 reply; 132+ results
From: Sarah Thomas @ 2002-11-14 13:40 UTC (permalink / raw)


Interesting follow ups! thanks for the input and help ! 
I have succesfully extracted words from a string.
I read each line in from the file
and used find_token, followed by slice, followed by deleting the word
from the string..and then stored them in a fixed array for now..
this is just an outline of how i did it.....

loop
	Find_Token(Temp, Ada.Strings.Maps.To_Set(Ada.Characters.Latin_1.HT),
Ada.Strings.Outside, From, To);
	exit when To = 0;
		
	My_word := To_Unbounded_String(Slice(Temp, From, To));
	Put_line(Output_File,To_String(My_word));

	IF (Length(temp) /= To ) then
		Delete(Temp, 1, To + 1);
	else
		Delete(Temp, 1, To);
	end if;
			
	Store_data(Line_Number,Word_Number) := (My_Word);
			
end loop;



^ permalink raw reply	[relevance 5%]

* Overloading one instance of a dispatching function
@ 2002-09-26 17:52  4% Vincent Smeets
  0 siblings, 0 replies; 132+ results
From: Vincent Smeets @ 2002-09-26 17:52 UTC (permalink / raw)


Hallo,

I am trying to make an implementation of the ABNF syntax defined in RFC2234.
It defines rules for parsing mail messages. Here are some examples:

    BIT  = "0" / "1"    ; Character "0" or character "1"
    CRLF = CR LF        ; Rule CR followed by rule LF
    X    = BIT / CRLF   ; Rule BIT or rule CRLF

I have added my source code so far. A rule is implemented as an tagged type,
a character rule as a Character_Set and an alternation of rules by a record
with class wide pointers.

The "or"-operation for two rules works OK, but I want to optimize the case
that the "or"-opration is used for two Character_Set's. This case can
produce a new Character_Set with the characters from both Character_Set's. I
have tryed to solve this problem by adding a function to the specification:

   function "or" (Left, Right : in Character_Set) return Character_Set;

This gives a problem at the place where I am using the "or"-operator. The
compiler can't resolve which "or"-operator has to be used because both
"or"-operators match by type. I would suspect (and hoped) that an exact type
(like Character_Set) had an higher precedance than a class wide type (like
Rule'Class), but it isn't. :-(

How can I solve this problem? I would like to optimize the "or" for two
Character_Set's but don't want to require that the user has to classify
which "or" he will use.

Thanks,
Vincent

PS: This is no homework. See news:ajrisv$lc9$03$1@news.t-online.com

----------------------------------------------------------------------------
with Ada.Finalization;
with Ada.Strings.Maps;
with Ada.Strings.Unbounded;

package ABNF is

   type Rule is abstract tagged private;

   type Alternative is abstract new Rule with private;
   function "or" (Left, Right : in Rule'Class) return Alternative'Class;

   type Character_Set is new Alternative with private;
   function "or" (Left, Right : in Character_Set) return Character_Set;

   function To_Rule (Item : in Character) return Character_Set;

   type Concatination is new Rule with private;
   function "and" (Left, Right : in Rule'Class) return Concatination;

private

   type Rule is abstract new Ada.Finalization.Controlled with null record;
   type Rule_Access is access Rule'Class;

   type Alternative is abstract new Rule with null record;

   type Alternative_Rule is new Alternative with
      record
         Left, Right : Rule_Access;
      end record;
   --  procedure Adjust (Item : in out Alternative_Rule);
   --  procedure Finalize (Item : in out Alternative_Rule);

   type Character_Set is new Alternative with
      record
         Set : Ada.Strings.Maps.Character_Set;
      end record;

   type Concatination is new Rule with
      record
         Left, Right : Rule_Access;
      end record;
   --  procedure Adjust (Item : in out Concatination);
   --  procedure Finalize (Item : in out Concatination);

end ABNF;

----------------------------------------------------------------------------
with ABNF;
pragma Elaborate_All (ABNF);

procedure Forward_PGP is
   use ABNF;

   A : constant ABNF.Rule'Class :=
      ABNF.To_Rule ('a') or
      ABNF.To_Rule ('A');
   AB : constant ABNF.Rule'Class :=
      A and
      ABNF.To_Rule ('b');
   AC : constant ABNF.Rule'Class :=
      A and
      ABNF.To_Rule ('C');
   AB_AC : constant ABNF.Rule'Class :=
      AB or AC;
begin
   null;
end Forward_PGP;






^ permalink raw reply	[relevance 4%]

* Re: FAQ and string functions
  @ 2002-07-31  9:04  6%     ` Lutz Donnerhacke
  0 siblings, 0 replies; 132+ results
From: Lutz Donnerhacke @ 2002-07-31  9:04 UTC (permalink / raw)


* Oleg Goodyckov wrote:
>Perl we say @list=split(/ /,String) and that's all.  Is this Perl's own
>especiality? No. It can be realized in Ada. And I say more - without this
>Ada will never be convinient language. While for splitting string like
>"x=2*3" people will must be to write program enstead split("=","x=2*3"),
>people will write in Perl, not Ada.

Split is a library function in Perl, not a system call. You can have this
library call in Ada, too. Do you consider Perl unusable because MIME::Parser
is not in the core language?

\f
with Split, Ada.Text_IO, Whole;

procedure Test_Split is
   function Get_Whole_Line is new Whole.Line (Ada.Text_IO.Get_Line);
begin
   loop
      declare
         line : constant String := Get_Whole_Line;
         rang : constant Split.String_Ranges := Split.Split (' ', line);
      begin
         Ada.Text_IO.Put_Line ("Words:" & Integer'Image (rang'Length));
         for i in rang'Range loop
            Ada.Text_IO.Put (line (rang (i).first .. rang (i).last));
            if i < rang'Last then
               Ada.Text_IO.Put (", ");
            end if;
         end loop;
         Ada.Text_IO.New_Line;
      end;
   end loop;
exception
   when Ada.Text_IO.End_Error => null;
end Test_Split;
\f
with Ada.Strings.Maps;

package Split is
   pragma Preelaborate (Split);

   type Ranges is record
      first : Positive;
      last  : Positive;
   end record;
   type String_Ranges is array (Positive range <>) of Ranges;

   function Split (
     Source : String;
     Set    : Ada.Strings.Maps.Character_Set;
     Test   : Ada.Strings.Membership
   ) return String_Ranges;

   function Split (Terminator : Character; Source : String)
     return String_Ranges;
end Split;
\f
with Ada.Strings.Fixed;

package body Split is
   Null_Ranges : String_Ranges (Positive'First .. Positive'First - 1);

   function Split (Source : String;
     Set    : Ada.Strings.Maps.Character_Set;
     Test   : Ada.Strings.Membership) return String_Ranges is
      First, Last : Natural;
   begin
      Ada.Strings.Fixed.Find_Token (Source, Set, Test, First, Last);
      if Last = Natural'First then
         return Null_Ranges;
      else
         return Ranges'(First, Last) &
           Split (Source (Last + 1 .. Source'Last), Set, Test);
      end if;
   end Split;

   function Split (Terminator : Character; Source : String)
     return String_Ranges is
   begin
      return Split (Source,
        Ada.Strings.Maps.To_Set (Terminator), Ada.Strings.Outside);
   end Split;
end Split;
\f
package Whole is
   pragma Preelaborate (Whole);

   buffsize : Positive := 80;

   generic
      with procedure Get (buff : out String; last : out Natural);
   function Line return String;
end Whole;
\f
package body Whole is
   function Line return String is
      buff : String (Positive'First .. Positive'First + buffsize);
      last : Natural;
   begin
      Get (buff, last);
      if last < buff'Last then
         return buff (buff'First .. last);
      else
         return buff & Line;
      end if;
   end Line;
end Whole;



^ permalink raw reply	[relevance 6%]

* Re: Subtypes with Combined Ranges
  @ 2002-07-18 13:15  4% ` Lutz Donnerhacke
  0 siblings, 0 replies; 132+ results
From: Lutz Donnerhacke @ 2002-07-18 13:15 UTC (permalink / raw)


* David Rasmussen wrote:
>6.1 Write a program to count the number of occurrences of each letter of
>    the alphabet typed as input at the keyboard. Using a subtype of
>    Character as the index subtype of an array is a sensible way to do
>    this.

>My first thought was to do this:
>subtype Alphabetical is Character range 'A'..'Z' | 'a'..'z';

A subtype has to be holefree.

>But I get an error. What is the best type for this excercise?

There are multiple solutions:
  - subtype Uppercase is Character range 'A' .. 'Z';
    subtype Lowercase is Character range 'a' .. 'z';
  - lettertest : array (Character) of Boolean :=
      ('A' .. 'Z' | 'a' .. 'z' => True, others => False);
  - lettermap : Ada.Strings.Maps.Character_Set :=
      To_Set (((Low => 'a', High => 'z'), (Low => 'A', High => 'Z')));
  - and many more.

Because you post your exercise here, you will get an other one:
 Implement at least ten different algorithms which print the elementary
 multiplication table. Post them here in two weeks.
 



^ permalink raw reply	[relevance 4%]

* Re: config files proposal
  2002-06-04 19:55  5%         ` Ted Dennison
@ 2002-06-09 20:43  0%           ` Stephen Leake
  0 siblings, 0 replies; 132+ results
From: Stephen Leake @ 2002-06-09 20:43 UTC (permalink / raw)


dennison@telepath.com (Ted Dennison) writes:

> Darren New <dnew@san.rr.com> wrote in message
> news:<3CFB94A7.A455B8DD@san.rr.com>... 
> > I think they should be case sensitive unless there's a standard way of
> > converting uppercase unicode to lowercase unicode in Ada's libraries.
> 
> We need to match up well with what's in the Ada standard I think. 
> 
> The Ada standard has an Ada.Strings.Maps.Constants.Lower_Case_Map and
> an Ada.Strings.Wide_Maps.Wide_Constants.Lower_Case_Map. There is no
> reason why we can't define things to say that keys will be fed through
> the appropriate Lower_Case_Map before being matched.

Good point.

> If the language itself has some kind of problem with
> Ada.Strings.Wide_Maps.Wide_Constants.Lower_Case_Map, I say that is
> the language's problem, and outside the scope of a configuration
> item facility to try to worry about fixing. As long as we define
> what we are doing carfully this way, it is still explicit. If we
> stick to using the standard library, things should at least behave
> for people the way they have come to expect them to behave when
> using Ada.

According to my interpretation of recent posts by Robert Dewar (is
that qualified enough :), there is very little use of Wide_String. So
it's not clear whether Lower_Case_Map is "what people expect". But I
agree it would be a good place to start. 

Perhaps case sensitivity should be an option in the config file API.

-- 
-- Stephe



^ permalink raw reply	[relevance 0%]

* Re: config files proposal
  @ 2002-06-04 19:55  5%         ` Ted Dennison
  2002-06-09 20:43  0%           ` Stephen Leake
  0 siblings, 1 reply; 132+ results
From: Ted Dennison @ 2002-06-04 19:55 UTC (permalink / raw)


Darren New <dnew@san.rr.com> wrote in message news:<3CFB94A7.A455B8DD@san.rr.com>...
> I think they should be case sensitive unless there's a standard way of
> converting uppercase unicode to lowercase unicode in Ada's libraries.

We need to match up well with what's in the Ada standard I think. 

The Ada standard has an Ada.Strings.Maps.Constants.Lower_Case_Map and
an Ada.Strings.Wide_Maps.Wide_Constants.Lower_Case_Map. There is no
reason why we can't define things to say that keys will be fed through
the appropriate Lower_Case_Map before being matched.

If the language itself has some kind of problem with
Ada.Strings.Wide_Maps.Wide_Constants.Lower_Case_Map, I say that is the
language's problem, and outside the scope of a configuration item
facility to try to worry about fixing. As long as we define what we
are doing carfully this way, it is still explicit. If we stick to
using the standard library, things should at least behave for people
the way they have come to expect them to behave when using Ada.

-- 
T.E.D. 
Home     -  mailto:dennison@telepath.com (Yahoo: Ted_Dennison)
Homepage -  http://www.telepath.com/dennison/Ted/TED.html



^ permalink raw reply	[relevance 5%]

* Re: An example was Re: Tokens
  @ 2002-05-20  3:44  6%         ` David C. Hoos, Sr.
  0 siblings, 0 replies; 132+ results
From: David C. Hoos, Sr. @ 2002-05-20  3:44 UTC (permalink / raw)



----- Original Message -----
From: "chris.danx" <spamoff.danx@ntlworld.com>
Newsgroups: comp.lang.ada
To: <comp.lang.ada@ada.eu.org>
Sent: May 19, 2002 6:30 PM
Subject: Re: An example was Re: Tokens


>
> "chris.danx" <spamoff.danx@ntlworld.com> wrote in message
> news:dkWF8.34770$Iv.4001930@news6-win.server.ntlworld.com...
>
> Hi,
>
> Is there a cheap way to prevent the last "&" from being printed in the code
> below?  I can think of several options but all of them require an additional
> call to find_token or switching to a loop.  Is there another way that
> doesn't have a repeated call to find token?

Here is a more elegant example that I assert is more generally useful, as it
simply returns an array containing the first and last characters of each
token meeting the criterion.  The result can then be used to access the
tokens individually.

with Ada.Strings.Fixed;
with Ada.Strings.Maps;
with Ada.Text_IO;
procedure Test_Token_Limits is

   type Limits is record
      First : Positive;
      Last  : Natural;
   end record;

   type Limits_Array is array (Positive range <>) of Limits;

   function Token_Limits
     (Source     : String;
      Delimiters : Ada.Strings.Maps.Character_Set)
     return Limits_Array is
      The_Limits : Limits;
   begin
      Ada.Strings.Fixed.Find_Token
        (Source,
         Delimiters,
         Ada.Strings.Outside,
         The_Limits.First,
         The_Limits.Last);
      if The_Limits.Last /= 0 then
         return The_Limits & Token_Limits
           (Source (The_Limits.Last + 1 .. Source'Last), Delimiters);
      else
         return Limits_Array'(1 .. 0 => The_Limits);
      end if;
   end Token_Limits;

   Delimiters : constant Ada.Strings.Maps.Character_Set :=
     Ada.Strings.Maps.To_Set (" !?,:;.");

   Source : constant String := "Now is the time for all good men to " &
     "come to the aid of their country.";

   Word_Limits : constant Limits_Array := Token_Limits
     (Source     => Source,
      Delimiters => Delimiters);
begin
   for W in Word_Limits'Range loop
      Ada.Text_IO.Put_Line
        ("Word no." & W'Img & " is """ &
         Source (Word_Limits (W).First .. Word_Limits (W).Last) & """."
        );
   end loop;
end Test_Token_Limits;







^ permalink raw reply	[relevance 6%]

* Re: An example was Re: Tokens
  2002-05-19 23:13  6%     ` An example was Tokens chris.danx
  @ 2002-05-20  1:36  0%       ` ProLogic
  1 sibling, 0 replies; 132+ results
From: ProLogic @ 2002-05-20  1:36 UTC (permalink / raw)


Thanks chris. Recusion is fine.

"chris.danx" <spamoff.danx@ntlworld.com> wrote in message
news:dkWF8.34770$Iv.4001930@news6-win.server.ntlworld.com...
>
> "ProLogic" <ProLogic@prologitech.ods.org> wrote in message
> news:3ce81da1$1@news.comindico.com.au...
> > Could I you show me a working example of this please? I've read that
> entire
> > section you have shown me, hmmm
>
> This is a quicky example I wrote in 10mins.  It uses recursion which I
think
> is clearer in this example, but if it's not clear what is going on I'll
> rewrite it with a loop no bother.
>
> If OE mangles it, send me an email (change spamoff to chris)
>
> HTH,
> Chris
>
>
> with ada.strings.fixed;  -- find_token is here;
> with ada.strings.maps;   -- character_set is here;
> with ada.text_io;
>
> use ada.strings;         -- outside/inside are here;
>
> procedure token_example is
>
>    -- prints all the "words" in a string, where
>    -- delims is the set of characters regarded as whitespace.
>    --
>    procedure what_words (str    : in string;
>                          delims : in maps.character_set) is
>       first : positive := 1;
>       last  : natural := 0;
>    begin
>       fixed.find_token (str,
>                         delims,
>                         ada.strings.outside,
>                         first,
>                         last);
>
>       -- if last = 0 there are no more tokens, so we stop,
>       -- otherwise we recur!
>       --
>       if last > 0 then
>          ada.text_io.put (str(first..last) & " & ");
>
>          what_words (str (last + 1..str'last),
>                      delims);
>       end if;
>    end what_words;
>
>    -- a simple character set!
>    --
>    something_simple : maps.character_set := maps.to_set (" !?,");
>
> begin
>    what_words ("My name is bob! And I like skinny dipping parties how
about
> you?",
>                something_simple);
> end token_example;
>
>
>
>
>





^ permalink raw reply	[relevance 0%]

* An example was Re: Tokens
  @ 2002-05-19 23:13  6%     ` chris.danx
    2002-05-20  1:36  0%       ` ProLogic
  0 siblings, 2 replies; 132+ results
From: chris.danx @ 2002-05-19 23:13 UTC (permalink / raw)



"ProLogic" <ProLogic@prologitech.ods.org> wrote in message
news:3ce81da1$1@news.comindico.com.au...
> Could I you show me a working example of this please? I've read that
entire
> section you have shown me, hmmm

This is a quicky example I wrote in 10mins.  It uses recursion which I think
is clearer in this example, but if it's not clear what is going on I'll
rewrite it with a loop no bother.

If OE mangles it, send me an email (change spamoff to chris)

HTH,
Chris


with ada.strings.fixed;  -- find_token is here;
with ada.strings.maps;   -- character_set is here;
with ada.text_io;

use ada.strings;         -- outside/inside are here;

procedure token_example is

   -- prints all the "words" in a string, where
   -- delims is the set of characters regarded as whitespace.
   --
   procedure what_words (str    : in string;
                         delims : in maps.character_set) is
      first : positive := 1;
      last  : natural := 0;
   begin
      fixed.find_token (str,
                        delims,
                        ada.strings.outside,
                        first,
                        last);

      -- if last = 0 there are no more tokens, so we stop,
      -- otherwise we recur!
      --
      if last > 0 then
         ada.text_io.put (str(first..last) & " & ");

         what_words (str (last + 1..str'last),
                     delims);
      end if;
   end what_words;

   -- a simple character set!
   --
   something_simple : maps.character_set := maps.to_set (" !?,");

begin
   what_words ("My name is bob! And I like skinny dipping parties how about
you?",
               something_simple);
end token_example;








^ permalink raw reply	[relevance 6%]

* Re: Newbie question
  @ 2002-01-01 21:26  6%             ` Michal Nowak
  0 siblings, 0 replies; 132+ results
From: Michal Nowak @ 2002-01-01 21:26 UTC (permalink / raw)
  To: comp.lang.ada usegroup->mailing list gateway

On 01-12-31 at 17:51 Jasbinder S Uppal wrote:

[snip]

>PS Michal hope ur feeling better, if not, a dose of Ada will certainly fix
>any ailments u have.....

Thank you sincerely, I'm OK now. I'm glad I've been a bit helpful. I hope
that the errors I made did not confused you. I'm newbie also...My advices
were a bit in C-tone, I wasn't well aware of Ada strings. I learned a bit
more when I was lying in bed and reading Cohen's book. Maybe this will be
more helpful than my last "advices".
If you have access to Reference Manual (HTML files are installed with GNAT,
so you should), look at Annex A, section 4 (particularly 4.2).
There is useful package Ada.Strings.Maps and Ada.Strings.Fixed (the latter
in case if you use fixed length Strings). It will be much easir to parse
the input line using functions and procedures from these packages. I think
that procedure Find_Token will be helpful. A token can be a sequence of
characters belonging to some set. The second parameter of Find_Token is of
type Character_Set. As I remember, the first word was the name of place
(so it consists of upper and lowercase letters) and the second was road
number (consisting of letters and numbers) and the rest was hour (only
numbers). In Ada.Strings.Maps.Constants there are predefined sets of
chracters:
Alphanumeric_Set : ISO-8859-1 letters and numbers,
Letter_Set : ISO-8859-1 letters,
Decimal_Digit_Set : Decimal numbers.

Alphanumeric_Set consists not only Enlish letters, but also letters with
diacritical marks. This piece of code shows chracters from this set:

with Ada.Strings.Maps.Constants;
    use Ada.Strings.Maps;  --for procedures
    use Ada.Strings.Maps.Constants; --for constant sets
with Ada.Text_IO;
    use Ada.Text_IO;

procedure Show_Set is
begin
    Put (To_Sequence(Alphanumeric_Set) );
end Show_Set;

If you apply Find_Token to extracting values, all can be written
like this:
Find_Token (Input_Line, Letter_Set, Inside, From, To);

In From and To variables you will get beginning and end of first
word. You may than use slice operation to get the first word into
string:
Place := To_Unbounded_String (Input_Line (From .. To) );
(I assume here, that place is of type Unbounded_String, declared in
Ada.Strings.Unbounded, you may need to "with" this package);

Than you may repeat the search for the second word:
Find_Token (Input_Line (To + 1 .. Input_Line'Last), Letter_Set, Inside, From, To);
                        ^^
     This To was obtained in first call to Find_Token.

And then extract the second word and do the same for numbers.

I hope I was more helpful now and that I was not to late.
Enjoy,
Mike(
-----------------------------------------
                             ____|
                             \%/ |~~\
  O                                  |
 o>>        Mike Nowak               |
 T                                   |
/ >       vinnie@inetia.pl           |
http://www.geocities.com/vinnie14pl _|__




^ permalink raw reply	[relevance 6%]

* Re: List Container Strawman 1.4
  2001-12-15 20:29  0%       ` Ted Dennison
@ 2001-12-16 18:45  0%         ` Nick Roberts
  0 siblings, 0 replies; 132+ results
From: Nick Roberts @ 2001-12-16 18:45 UTC (permalink / raw)


"Ted Dennison" <dennison@telepath.com> wrote in message
news:koOS7.73$XC5.37@www.newsranger.com...

> >I've fixed that. For unbounded lists, the user can have up to 255 cursors
> >(iterators), dynamically allocated, which can be dynamically varied. The
> >limit of 255 is arbitrary, and could be increased if you think it
necessary.
>
> I don't think that really addresses the concern, which is that this isn't
really
> an "unbounded" approach.

Ted, what are you getting at, really? I don't give a flying Dan Quail
whether it is or isn't, in some higher Zen way, an unbounded approach. Isn't
the point simply that the user can have as many cursors (iterators) as she
requires?

> Not that I'm a huge fan of the approach the current
> strawman uses either. If you've been reading a while, you know I'd lean
towards
> making the users responsible for iterator safety. But the current approach
is
> the only one that we have been able to get general agreement on.

Frankly, I'm more interested in getting your agreement than anyone else's
(at this point). Are you saying you personally favour my approach? Since it
looks like we two are going to be producing this facility, who else has a
more important opinion? If other people don't like it, it's up to them to
make a noise.

> If you could
> convince folks that your (hugely) bounded approach was the way to go, I'd
> certianly put that in instead. But so far I see absolutely no sign of that
> happening. Not a single other person has come out in support of it in two
weeks,
> and I see no evidence that this situation would change if we were to delay
> things another two weeks.

On the other hand, why don't we do it my way, and see how many people
complain? I don't think anyone actually would.

> >The fact that an array version is included for each operation that has a
> >secondary data parameter is not just nice, it is necessary for the sake
of
> >efficiency. Consider the extra work done by converting the array to a
list,
> >and then applying that list.
>
> That's only an issue if you don't have the Strawman's "Splice" routine.

I don't think so. I can see it helps for insertion, but not for replacement.
Besides which, you seem to be advocating making a user do this:

   declare
      Temp: x.List := To(("Alice","Jenny","Frida"));
      It: Iterator := Side(Invitees,Back);
   begin
      Splice(Temp,It);
   end;

when my package would permit:

   Append(Invitees,("Alice","Jenny","Frida"));

You've got to admit, the latter is a bit easier, huh?

> >[1] I would prefer the name 'Element_Type' to 'Element' for the generic
> >parameter, since 'Element_Type' is what Ada.Sequential_IO and
Ada.Direct_IO
> >use.
>
> My opinion on the stupidity of "_Type" is probably well known by now. If
we were
> trying to emulate either of those packages in other ways, or there was a
good
> case for it possibly causing confusion, then it might be worth using
"_Type"
> regardless. But I don't believe either is the case here.

I agree it's stupid, but if we start trying to correct all the stupid things
in Ada, we might just as well start inventing a new language. I really think
most users are not going to say "Oh goody, how great that they changed all
the naming conventions to something better!". I think most would say "Oh
******* ****, they've changed all the ******* naming conventions to
something different to the rest of Ada!" Specifically, if the name 'Element'
is used for the data type (instead of 'Element_Type') that means the
function which retrieves an element cannot be named 'Element', which is the
name of the analogous function in Ada.Strings.*ounded.

> >[2] I would prefer a name other than 'List' for the list type, since
'List'
> >seems to be such a natural name for parameters and objects of a list type
>
> That issue (type vs. object naming guidelines) has been thouroughly
discussed
> already a week and a half ago. General names like "List" are for types,
while
> objects (and parameters) should be named something more specific that
designates
> either exactly what the object is, or what its role in the system is (eg:
> "Target"). This isn't just some rule I made up. The Ada Quality and Style
guide
> phrases it this way:
>
> * Use singular, general nouns as subtype identifiers. (3.2.2 - Subtype
Names)
> * Choose identifiers that describe the object's value during execution.
(3.2.3 -
> Object Names)
>
> You seem to worry that this will cause problems, but we already have a
package
> spec and it hasn't caused problems that I can see. I'm thinking we can get
by
> just fine in the body too. Those are the only places it should be an
issue, as
> everywhere else dot notation can be used to disambiguate.

Nicely argued, and I concede. Type names such as 'List', 'Set', and 'Contar'
(or 'Lookup'?) are reasonably appropriate in a generic package, since they
will indeed tend to be either qualified or renamed (by a subtype
declaration).

> >[4] If you consider their usage, the functions 'To' and 'From' are surely
> >confusingly named. What is wrong with 'To_List' and 'To_Array' (or
similar)?
>
> That may be a bit of an issue. I general I think things should be named
relative
> to the package name. If one uses full dot notation, things look great this
way.
> However, in this case it might be a bit obscure without it:
>
> Foo_List := To (Foo_Items);
>
> and
>
> Foo_Items := From (Foo_List)
>
> The flip answer to this it to use the package names anyway if it doesn't
look
> clear without them. However, it would perhaps be nice if things aren't
quite so
> obtuse without them.

   Foo_List  := To_List  (Foo_Items);
   Foo_Items := To_Array (Foo_List);

This seems a lot better to me.

   Foo_List  := Foo_Lists.To_List  (Foo_Items);
   Foo_Items := Foo_Lists.To_Array (Foo_List);

And this is perfectly okay, isn't it?

> >[5] Analogous to the Ada.Strings.Maps.To_Set function, the function
> >'Singleton' should be named more like 'To_List' with a parameter named
> >'Singleton'.
>
> I could see it as an overload of the "To" function, or whatever we end up
naming
> it. But its not that big of a deal either way.

So is that a "yes" then? ;-)

> >[6] I think it would probably (but not necessarily) be better to have the
> >list exceptions gathered into the x.Lists parent package, so that there
is
> >only one of each exception (rather than one for each instantiation of
> >x.Lists.[Unb|B]ounded).
>
> That's most likely true. When we have more than one package we can do
that.

No time like the present. Let's do it now.

> >[7] As mentioned, I actually want to remove directional parameters.
Instead,
> >all that is required is a 'smart reverse' operation. This merely switches
an
> >'effective forwardness' flip-flop between actually forward and actually
> >backward. All the operations must be programmed to behave according to
the
> >effective forwardness (not difficult).
>
> I'd like to see this,

All that is required is that the pair of pointers in each node, cursor, and
the base, are made into a duple (array):

   type Direction is (Forward, Backward);
   type Ref_Pair is array (Direction) of Node_Ref;

Then the base has a component that indicates the current 'sense' of the
list:

   EF: Direction; -- Effective Forward

All operations then simply refer to L.Ref(L.EF) to get the 'current forward'
node pointer, and L.Ref(Opposite(L.EF)) to get the 'current backward' one.
(of course, one might have two components, EF and EB.) To apparently reverse
the list, all you do is reverse (set to its opposite) EF (and EB).

> but I should note that the less state-full calls are, the
> easier they will be to parralelize.

Fair point in general, but I think you will find that it is very rare, in
practice, for a list to be operated on in parallel (conversely, a slightly
different idiom, the queue, is used almost exclusively in parallel). By
contrast, sets and contars (and others) are often used in parallel. It's one
of those little oddities.

> I also get worried whenever I hear anyone
> use the word "smart" in the context of a computer program. :-)

You're quite right there, of course! It's only one short step away from
artificial intelligence, and we all know where that leads to. :-)

> (several other parameter naming issues removed)
> I'll look into the merits of all these. I don't think we should let
parameter
> names hold up the works at this point though. We'll never get everyone to
agree
> that they are all perfect.

As I say, never mind anyone else. Let's agree between ourselves, and let's
do it now (it's easier that way).

> >[13] I have a problem with passive iterators. Texts say that they should
be
> >provided in addition to active iterators, but I rather feel this is like
>
> Frankly I totally agree with you here. I don't like to use them either.
But
> several people here do, and were quite insistent that they need to be in
there.
> Since it doesn't seriously hurt anything to put one in (its not like it
has
> cascading effects throughout the whole package), I can't really see
keeping them
> out just because the two of us don't like to use them.

Reluctuantly accepted.

> >[14] I feel that the term 'iterator' should be reserved for a construct
that
> >is applicable to all container types (and which is therefore
monodirectional
>
> Since we don't and won't have such a thing, I don't see the sense in
reserving
> the term for that.

This is extremely important, to me. Could you explain why you don't want
container-wide iterators? It seems like a bizarre attitude, to be frank.
Remember, the STL iterators are all container-wide, and I believe this was a
fundamental design decision.

> >[15] The reason why I made cursors internal to list objects (rather than
> >providing a separate cursor type) is because an operation on one cursor
> >(active on a certain list object) must be able to interrogate and
possibly
> >update any other cursors (also active on the same list object). With
> >separate cursor objects, the only way to do this is for each cursor to
> >contain a pointer to the list it is active on, and for each list to
contain
> >pointers (perhaps in a linked list) to all the cursors active on it. This
>
> That's correct, but what it ultimately requires is that both lists and
active
> iterators be controlled. I can show the implementation in detail, but the
work
> required is roughly equivalent to providing a body for this package, which
is
> what we were discussing doing in the first place.

I don't think this issue really has anything to do with controlledness
(although the two issues do touch upon one another, they do so only
incidentally). Again, it sounds like you are actually agreeing with me. Are
you?

> Fine rationale aside, it appears we have already reached a consensus on
using
> the controlled iterator approach. The issue under consideration isn't if
someone
> has another approach which they can argue is better. Clearly you feel you
do.
> The issue is what we can move forward with. The approach you describe is
not
> substantially different from the one you presented 2 weeks ago, and the
fact of
> the matter is that people, for whatever reason, have not been rallying
around
> it. I don't see any hope in the tide turning in its favor if we wait
another 2-4
> weeks.

Again, why don't we do it my way, and see how many other people complain?

> The strawman has presented 3 different active iterator approaches (each
> progressively further from my "ideal" btw). The final one seems to be the
one
> people want. I'm not nessecarily any happier about that than you are, but
that's
> the way it has worked out.

So, go for a design you are happier about! :-)

> >[20] What does Splice do? Is it useful?
>
> See *waaay* previously. I cribbed it from the STL. Its essential for
efficiently
> putting two lists together.

Aha! A destructive insert. Handy. (Added to my package ;-)

> >[21] Why do you provide list serialisation (stream read and write)
> >procedures in public, rather than overriding the Read and Write
attributes
> >of the list type in private?
>
> I've had problems (of an exact nature that I forget) when they were
private. So
> that's just become my idiom. It could be that the routines could be moved
to
> just inside of the private section without hurting anything. I'll check it
out
> when I get a chance.

All you have to do is declare in the private part:

   type List is new Ada.Finalization.Controlled with
      record
         ...
      end record;

   procedure Read_List (
         Stream : access Ada.Streams.Root_Stream_Type'Class;
         Item   :    out List );

   procedure Write_List (
         Stream : access Ada.Streams.Root_Stream_Type'Class;
         Item   : in     List );

   for List'Read  use Read_List;
   for List'Write use Write_List;

and then provide bodies for Read_List and Write_List in the package body.
Job done and dusted.

> >Your proposal apparently omits the following vital operations: [22]
testing
> ..
> I don't personally consider any of this "vital", and much of it can be
done just
> fine with an iterator, along with loads of other stuff you haven't thought
of
> but someone somewhere else considers vital. :-)

I readily agree with the point that one could indeed go on and on forever
adding useful operations. But you are wrong that the operations I mentioned
can be done "perfectly well" with an iterator. They cannot: the equivalent
operations done with an iterator would be significantly less efficient (as
well as less convenient).

> >[29] Although you have put some documentation into the spec as comments,
it
> >is not quite as clear or complete as would be ideal. I think it might be
> >helpful if this documentation were separated out into a text (or HTML)
file.
>
> I agree with this wholeheartedly. I already have one volunteer to work up
some
> documentation. Unfortunately, he prefers to work in Word instead of
HTML(yuk).
> But word is (arguably) better than nothing. :-)

Splendid.

> You do point out some issues which I think need to be addressed. But the
only
> ones I'd consider major are issues where it appears we already have a fair
> amount of consensus on. The rest is just naming issues.

Well, to recap: I think the most important consensus is between us two (at
the moment); I think naming issues are pretty important (but true everything
is relative); I think it's important to pin down the spec as best we can
early on, so as not to give the documentor a moving target, and so as not to
give ourselves a moving target writing the sample implementation.

> >Any more thoughts on a (better) name for the project? (Does 'Tenet'
tickle
> >you at all?)
> Perhaps my tonsils a bit. :-)
>
> I'm still stuck on the palindrome issue. Unfortunately, palindromes are
one of
> the tougher word tricks to work out, so there aren't that many to choose
from.
> Since Anna is taken, I'd kind of like "ANA" (if someone can get a decent
acronym
> for it), or "Elle" or "Ele" for personal reasons.

Extended Language Library Endeavour (ELLE) would be fine by me (base package
name 'Elle'). Pretty good, really.

> ---
> T.E.D.    homepage   - http://www.telepath.com/dennison/Ted/TED.html

--
Best wishes,
Nick Roberts






^ permalink raw reply	[relevance 0%]

* Re: List Container Strawman 1.4
  2001-12-15  1:20  2%     ` Nick Roberts
@ 2001-12-15 20:29  0%       ` Ted Dennison
  2001-12-16 18:45  0%         ` Nick Roberts
  0 siblings, 1 reply; 132+ results
From: Ted Dennison @ 2001-12-15 20:29 UTC (permalink / raw)


In article <9ve8jn$esilp$1@ID-25716.news.dfncis.de>, Nick Roberts says...
>
>"Ted Dennison" <dennison@telepath.com> wrote in message
>news:z9aN7.41127$xS6.69040@www.newsranger.com...
>
>> "unbounded" package, I don't think the user should have to worry about
>running
>> out of resources like iterators. That sort of breaks the whole "unbounded"
>> philosophy.
>
>I've fixed that. For unbounded lists, the user can have up to 255 cursors
>(iterators), dynamically allocated, which can be dynamically varied. The
>limit of 255 is arbitrary, and could be increased if you think it necessary.

I don't think that really addresses the concern, which is that this isn't really
an "unbounded" approach. Not that I'm a huge fan of the approach the current
strawman uses either. If you've been reading a while, you know I'd lean towards
making the users responsible for iterator safety. But the current approach is
the only one that we have been able to get general agreement on. If you could
convince folks that your (hugely) bounded approach was the way to go, I'd
certianly put that in instead. But so far I see absolutely no sign of that
happening. Not a single other person has come out in support of it in two weeks,
and I see no evidence that this situation would change if we were to delay
things another two weeks.


>The fact that an array version is included for each operation that has a
>secondary data parameter is not just nice, it is necessary for the sake of
>efficiency. Consider the extra work done by converting the array to a list,
>and then applying that list.

That's only an issue if you don't have the Strawman's "Splice" routine.

>I'm afraid I've got quite a few comments on your straw man as it is
>currently. Here goes.
>
>[1] I would prefer the name 'Element_Type' to 'Element' for the generic
>parameter, since 'Element_Type' is what Ada.Sequential_IO and Ada.Direct_IO
>use.

My opinion on the stupidity of "_Type" is probably well known by now. If we were
trying to emulate either of those packages in other ways, or there was a good
case for it possibly causing confusion, then it might be worth using "_Type"
regardless. But I don't believe either is the case here.

>[2] I would prefer a name other than 'List' for the list type, since 'List'
>seems to be such a natural name for parameters and objects of a list type

That issue (type vs. object naming guidelines) has been thouroughly discussed
already a week and a half ago. General names like "List" are for types, while
objects (and parameters) should be named something more specific that designates
either exactly what the object is, or what its role in the system is (eg:
"Target"). This isn't just some rule I made up. The Ada Quality and Style guide
phrases it this way:

* Use singular, general nouns as subtype identifiers. (3.2.2 - Subtype Names)
* Choose identifiers that describe the object's value during execution. (3.2.3 -
Object Names)

You seem to worry that this will cause problems, but we already have a package
spec and it hasn't caused problems that I can see. I'm thinking we can get by
just fine in the body too. Those are the only places it should be an issue, as
everywhere else dot notation can be used to disambiguate.  

>(not necessarily in the list package spec, but elsewhere). If the unbounded
>list package is going to be named 'x.Lists.Unbounded', it would seem natural
>to use the name 'Unbounded_List' (by analogy to
>Ada.Strings.Unbounded.Unbounded_List). I do feel that the need for
>consistency outweighs any complaint of wordiness.

If folks *really* want that, we can do it. But the current difference is quite
conscious. All things being equal, I'm in favor of keeping things consistent as
well. But in this case, all things aren't even close to equal. That naming
system (repeating the package name in the type name) was a tragic mistake, and I
for one am not in favor of spreading the cancer further throughout the standard
libraries in the name of consistency. 

>[3] Why is Element_Array declared with a Natural index subtype? Wouldn't
>Positive be more appropriate?

An oversight. You are quite correct. I'll fix it.

>[4] If you consider their usage, the functions 'To' and 'From' are surely
>confusingly named. What is wrong with 'To_List' and 'To_Array' (or similar)?

That may be a bit of an issue. I general I think things should be named relative
to the package name. If one uses full dot notation, things look great this way.
However, in this case it might be a bit obscure without it:

Foo_List := To (Foo_Items);

and

Foo_Items := From (Foo_List)

The flip answer to this it to use the package names anyway if it doesn't look
clear without them. However, it would perhaps be nice if things aren't quite so
obtuse without them.

>[5] Analogous to the Ada.Strings.Maps.To_Set function, the function
>'Singleton' should be named more like 'To_List' with a parameter named
>'Singleton'.

I could see it as an overload of the "To" function, or whatever we end up naming
it. But its not that big of a deal either way.

>[6] I think it would probably (but not necessarily) be better to have the
>list exceptions gathered into the x.Lists parent package, so that there is
>only one of each exception (rather than one for each instantiation of
>x.Lists.[Unb|B]ounded).

That's most likely true. When we have more than one package we can do that.

>[7] As mentioned, I actually want to remove directional parameters. Instead,
>all that is required is a 'smart reverse' operation. This merely switches an
>'effective forwardness' flip-flop between actually forward and actually
>backward. All the operations must be programmed to behave according to the
>effective forwardness (not difficult).

I'd like to see this, but I should note that the less state-full calls are, the
easier they will be to parralelize. I also get worried whenever I hear anyone
use the word "smart" in the context of a computer program. :-)

(several other parameter naming issues removed)
I'll look into the merits of all these. I don't think we should let parameter
names hold up the works at this point though. We'll never get everyone to agree
that they are all perfect.

>[12] I like the Remove procedure combining retrieval and deletion. This is
>an omission from my own proposal. [13] Maybe 'Old_Element' should be
>'Old_Item'. ([14] Also, I would prefer the name 'Extract' for the
>subprogram.)

I think I like that better too.

>
>Now we come to the vexed issue of iterators.
>
>[13] I have a problem with passive iterators. Texts say that they should be
>provided in addition to active iterators, but I rather feel this is like

Frankly I totally agree with you here. I don't like to use them either. But
several people here do, and were quite insistent that they need to be in there.
Since it doesn't seriously hurt anything to put one in (its not like it has
cascading effects throughout the whole package), I can't really see keeping them
out just because the two of us don't like to use them.

>[14] I feel that the term 'iterator' should be reserved for a construct that
>is applicable to all container types (and which is therefore monodirectional

Since we don't and won't have such a thing, I don't see the sense in reserving
the term for that. 

>[15] The reason why I made cursors internal to list objects (rather than
>providing a separate cursor type) is because an operation on one cursor
>(active on a certain list object) must be able to interrogate and possibly
>update any other cursors (also active on the same list object). With
>separate cursor objects, the only way to do this is for each cursor to
>contain a pointer to the list it is active on, and for each list to contain
>pointers (perhaps in a linked list) to all the cursors active on it. This

That's correct, but what it ultimately requires is that both lists and active
iterators be controlled. I can show the implementation in detail, but the work
required is roughly equivalent to providing a body for this package, which is
what we were discussing doing in the first place.

Fine rationale aside, it appears we have already reached a consensus on using
the controlled iterator approach. The issue under consideration isn't if someone
has another approach which they can argue is better. Clearly you feel you do.
The issue is what we can move forward with. The approach you describe is not
substantially different from the one you presented 2 weeks ago, and the fact of
the matter is that people, for whatever reason, have not been rallying around
it. I don't see any hope in the tide turning in its favor if we wait another 2-4
weeks. 

The strawman has presented 3 different active iterator approaches (each
progressively further from my "ideal" btw). The final one seems to be the one
people want. I'm not nessecarily any happier about that than you are, but that's
the way it has worked out.


>[20] What does Splice do? Is it useful?

See *waaay* previously. I cribbed it from the STL. Its essential for efficiently
putting two lists together.

>
>[21] Why do you provide list serialisation (stream read and write)
>procedures in public, rather than overriding the Read and Write attributes
>of the list type in private?

I've had problems (of an exact nature that I forget) when they were private. So
that's just become my idiom. It could be that the routines could be moved to
just inside of the private section without hurting anything. I'll check it out
when I get a chance.

>Your proposal apparently omits the following vital operations: [22] testing
..
I don't personally consider any of this "vital", and much of it can be done just
fine with an iterator, along with loads of other stuff you haven't thought of
but someone somewhere else considers vital. :-)

The exception is "=", which clearly needs to be redefined or removed. The
default is going to be nonsense.

>[29] Although you have put some documentation into the spec as comments, it
>is not quite as clear or complete as would be ideal. I think it might be
>helpful if this documentation were separated out into a text (or HTML) file.

I agree with this wholeheartedly. I already have one volunteer to work up some
documentation. Unfortunately, he prefers to work in Word instead of HTML(yuk).
But word is (arguably) better than nothing. :-)

You do point out some issues which I think need to be addressed. But the only
ones I'd consider major are issues where it appears we already have a fair
amount of consensus on. The rest is just naming issues.


>Any more thoughts on a (better) name for the project? (Does 'Tenet' tickle
>you at all?)
Perhaps my tonsils a bit. :-)

I'm still stuck on the palindrome issue. Unfortunately, palindromes are one of
the tougher word tricks to work out, so there aren't that many to choose from.
Since Anna is taken, I'd kind of like "ANA" (if someone can get a decent acronym
for it), or "Elle" or "Ele" for personal reasons.

---
T.E.D.    homepage   - http://www.telepath.com/dennison/Ted/TED.html

No trees were killed in the sending of this message. 
However a large number of electrons were terribly inconvenienced.



^ permalink raw reply	[relevance 0%]

* Re: List Container Strawman 1.4
  @ 2001-12-15  1:20  2%     ` Nick Roberts
  2001-12-15 20:29  0%       ` Ted Dennison
  0 siblings, 1 reply; 132+ results
From: Nick Roberts @ 2001-12-15  1:20 UTC (permalink / raw)


"Ted Dennison" <dennison@telepath.com> wrote in message
news:pMoS7.61491$xS6.100531@www.newsranger.com...

> However, there are some very good ideas in there, most notably the
unconstrained
> array conversions and the Direction type, that have made their way into
the
> Strawman.

Ironically, I want to remove the Forward parameters (of type Direction) from
all the operations (and replace the functionality with a 'smart reverse'
operation).

"Ted Dennison" <dennison@telepath.com> wrote in message
news:z9aN7.41127$xS6.69040@www.newsranger.com...

> On the other hand, I'm not a big fan of the iterator approach used. In an
> "unbounded" package, I don't think the user should have to worry about
running
> out of resources like iterators. That sort of breaks the whole "unbounded"
> philosophy.

I've fixed that. For unbounded lists, the user can have up to 255 cursors
(iterators), dynamically allocated, which can be dynamically varied. The
limit of 255 is arbitrary, and could be increased if you think it necessary.

> Also I think there are too many operations in there. The package spec is
huge.
> It has (by my count) 79 subprograms. The current strawman has 34, which to
some
> people it seems is annoyingly small, as we keep seeing suggestions for
> additions. Perhaps in between there somewhere the truth lies.

Ada.Strings.Unbounded has 62. Ada.Text_IO has 113. I would submit that 79 is
not huge, and (like lines or semicolons) is not a very good measure (of
complexity?) anyway. The number of really conceptually different operations
is around 20-30, and most of the concepts not too difficult.

> A large culprit here seems to be the unbounded-array support, which is
probably
> taken a bit too far. Its OK to convert between them, but anything much
more
> should probably be accomplished by first converting the array to a list.
If we
> take Ada.Strings.Unbounded as a model, only the infix operators should
have
> unbounded array equivalents.

The fact that an array version is included for each operation that has a
secondary data parameter is not just nice, it is necessary for the sake of
efficiency. Consider the extra work done by converting the array to a list,
and then applying that list.

"Ted Dennison" <dennison@telepath.com> wrote in message
news:pMoS7.61491$xS6.100531@www.newsranger.com...

> Excepting the stuff I have raised issues about, is there anything else in
there
> that you think really needs to be in the Strawman before we proceed?

I'm afraid I've got quite a few comments on your straw man as it is
currently. Here goes.

[1] I would prefer the name 'Element_Type' to 'Element' for the generic
parameter, since 'Element_Type' is what Ada.Sequential_IO and Ada.Direct_IO
use.

[2] I would prefer a name other than 'List' for the list type, since 'List'
seems to be such a natural name for parameters and objects of a list type
(not necessarily in the list package spec, but elsewhere). If the unbounded
list package is going to be named 'x.Lists.Unbounded', it would seem natural
to use the name 'Unbounded_List' (by analogy to
Ada.Strings.Unbounded.Unbounded_List). I do feel that the need for
consistency outweighs any complaint of wordiness.

[3] Why is Element_Array declared with a Natural index subtype? Wouldn't
Positive be more appropriate?

[4] If you consider their usage, the functions 'To' and 'From' are surely
confusingly named. What is wrong with 'To_List' and 'To_Array' (or similar)?

[5] Analogous to the Ada.Strings.Maps.To_Set function, the function
'Singleton' should be named more like 'To_List' with a parameter named
'Singleton'.

[6] I think it would probably (but not necessarily) be better to have the
list exceptions gathered into the x.Lists parent package, so that there is
only one of each exception (rather than one for each instantiation of
x.Lists.[Unb|B]ounded).

[7] As mentioned, I actually want to remove directional parameters. Instead,
all that is required is a 'smart reverse' operation. This merely switches an
'effective forwardness' flip-flop between actually forward and actually
backward. All the operations must be programmed to behave according to the
effective forwardness (not difficult).

[8] I would much prefer the 'Size' function to be named 'Length'. This would
be much more consistent with the use of the term size in the RM95 (and the
Size attribute), as well as the use of the term length, the Length attribute
of arrays, and the Length functions for Bounded and Unbounded strings.

[9] It would also be more consistent with Ada.Strings.* to use the parameter
name 'Source' rather than 'Subject'. [10] Similarly 'New_Item' rather than
'New_Element' (or 'New_Items'), and [11] 'Is_Null' for the function
'Is_Empty'.

[12] I like the Remove procedure combining retrieval and deletion. This is
an omission from my own proposal. [13] Maybe 'Old_Element' should be
'Old_Item'. ([14] Also, I would prefer the name 'Extract' for the
subprogram.)

Now we come to the vexed issue of iterators.

[13] I have a problem with passive iterators. Texts say that they should be
provided in addition to active iterators, but I rather feel this is like
providing cars with propellors and sails. Passive iterators have various
limitations that active iterators do not: an algorithm that has multiple
(significantly different) behaviour paths between iterations is much easier
to program with an active iterator; an algorithm that works with two or more
read-iterators is in general impossible to program with a passive iterator;
passive iterators do not permit arbitrary restarting; a passive iterator
cannot be a write-iterator. Passive iterators tend to break up the source
code associated with a particular algorithm or work chunk. Finally, a
passive iterator generic procedure can always be (very easily) constructed
from an active iterator. In computer science generally, arguments still rage
about this issue, but I'd give it the chop.

[14] I feel that the term 'iterator' should be reserved for a construct that
is applicable to all container types (and which is therefore monodirectional
and not repositionable, since reverse movement or repositioning would not be
appropriate to most containers), as this is the general use of the term (for
both Ada and other languages). This is why I chose the term 'cursor' (taken
from SQL) instead.

[15] The reason why I made cursors internal to list objects (rather than
providing a separate cursor type) is because an operation on one cursor
(active on a certain list object) must be able to interrogate and possibly
update any other cursors (also active on the same list object). With
separate cursor objects, the only way to do this is for each cursor to
contain a pointer to the list it is active on, and for each list to contain
pointers (perhaps in a linked list) to all the cursors active on it. This
would require the user to declare all list and cursor objects aliased, and
to somehow make the connection between cursor object and list object before
using a cursor. By having its cursors internal to the list object, all of
these inconveniences are removed.

[16] By making my cursors point inbetween items in the list, rather than at
items, various conceptual complications are clarified regarding deletion and
positioning at the end of the list. You do not appear to have adopted this
approach.

[17] My proposal provides a complete set of cursor operations. These include
element and array secondary data parameters. As mentioned, it is necessary
to provide all these operations, since they could not in general (depending
on the details of the implementation) be efficiently implemented otherwise.
[18] I also provide a complete set of absolute operations; I had thought
that it was agreed these were justified (if only just) on the grounds of
convenience. [19] I don't think it would be desirable for any of these
operations to be put into an inner package, because then they wouldn't be
inherited on derivatation of the list type (which is admittedly an unlikely
requirement, but possible).

[18] I have not published it yet, but I am going to add a child package
which provides an active iterator for lists. This iterator is of a type
derived from a container-wide iterator class, and forms part of an iteration
scheme that permits container-independent algorithms. This
container-independence is (according to texts on the subject) supposed to be
an essential aspect of (the advantage of using) iterators (and I agree).

[19] I'm also going to add a child package for sorting. The advantage (not
necessaily overwhelming) of using one of the predefined relative comparison
operators ("<", "<=", ">", ">=") for the ordering function is that you can
declare it "is <>" and save the instantiator having to specify this function
every time.

[20] What does Splice do? Is it useful?

[21] Why do you provide list serialisation (stream read and write)
procedures in public, rather than overriding the Read and Write attributes
of the list type in private?

Your proposal apparently omits the following vital operations: [22] testing
lists for equality; [23] exchanging lists; [24] exchanging two slices of a
list; [25] exchanging two elements of a list; [26] retrieval of a slice;
[27] deletion of a slice; [28] splitting a list into two (especially
destructively for a linked-list implementation).

[29] Although you have put some documentation into the spec as comments, it
is not quite as clear or complete as would be ideal. I think it might be
helpful if this documentation were separated out into a text (or HTML) file.
I must admit, the documentation file (HTML) that I cooked up for my own
proposal needs revision, simplification, and examples.

These points doubtless vary in importance, between 'not at all' to (I think)
'very'. Also, it has been demonstrated that I am not infallible :-) on
numerous occasions :-o ;-) However, I do feel that we are not quite yet at
the stage of going to a sample implementation.

I'm not concerned about whose proposal is developed, and I concede that
consensus means compromise, but I do feel that there are good reasons behind
the design of my proposal. What am I missing? (Apart, that is of course,
from charm, wit, courage, physique, generosity, humour, artistic
sensitivity, any kind of social grace whatsoever, ... ;-)

I really mean it when I say that I feel your input, as well as that of Jeff,
Mark, Stephe, and others, has prevented me from making an almighty cock-up
of the library I was going to (attempt to) build for AdaOS. For that I owe
you immense gratitude anyway. But I'm hoping that we can continue to make
progress together, Ted. After lists, I think we have sets, contars (or
whatever you want to call them), and probably many other things, to tackle.
I'd rather not do this alone.

Any more thoughts on a (better) name for the project? (Does 'Tenet' tickle
you at all?)

--
Best wishes,
Nick Roberts






^ permalink raw reply	[relevance 2%]

* Re:I'm baffled...
@ 2001-10-30 22:39  4% ANH_VO
  0 siblings, 0 replies; 132+ results
From: ANH_VO @ 2001-10-30 22:39 UTC (permalink / raw)
  To: comp.lang.ada

I am afraid that more codes need to be posted in order for me at least to find
out what is going on. In fact, it is not easy to reproduce the Constraint_Error
without knowing the exact Word_List.

Anh Vo

____________________Reply Separator____________________
Subject:    I'm baffled...
Author: Wes Groleau <wwgrol@sparc01.ftw.rsc.raytheon.com>
Date:       10/30/01 5:16 PM


Probably something simple, but I don't see it ....

I don't think it's a compiler bug because
I get the same error from Apex that I get from GNAT.

But how can I get a constraint_error on line 166
of ada.strings.maps?  That line is:
   Identity : constant Character_Mapping :=

I can't get either debugger to let me examine things
in the run-time.

Code excerpt:

   package ASF renames Ada.Strings.Fixed;
   package AS renames Ada.Strings;

   function Position_Of (Pattern : String) return Index is

      Result : Index := 47;
      -- just to make it any old legal value

      Checkpoint : Character := 'A';

   begin
      Checkpoint := 'B';
      Result := ASF.Index
                (Source  => Word_List (Current_Index + 1 ..
Word_List'Last),
                 Pattern => Pattern,
                 Going   => AS.Forward );
      Checkpoint := 'C';
      
      if Result /= 0 then
      Checkpoint := 'D';
         return Result;
      else
      Checkpoint := 'E';
         return ASF.Index
                (Source  => Word_List ( Word_List'First .. Current_Index
- 1),
                 Pattern => Pattern,
                 Going   => AS.Backward );
      Checkpoint := 'F';
      end if;
      Checkpoint := 'G';

   exception
      when E : others =>
        Ada.Text_IO.Put_Line (Ada.Exceptions.Exception_Information(E));
        Ada.Text_IO.Put_Line ("Checkpoint    => " & Checkpoint);
        Ada.Text_IO.Put_Line ("Context       => " & Word_List
(Current_Index - 10 .. Current_Index + 10) );
        Ada.Text_IO.Put_Line ("Pattern       => " & Pattern);
        Ada.Text_IO.Put_Line ("Current_Index => " & Integer'Image
(Current_Index));
        Ada.Text_IO.Put_Line ("Result        => " & Integer'Image
(Result));

      raise;

   end Position_Of;

Typical error output:

Exception name: CONSTRAINT_ERROR
Message: a-strmap.ads:166

Checkpoint    => B
Context       => addenda addendum adhe
Pattern       =>  pri
Current_Index =>  117947
Result        =>  47

(Word_List is a BIG string)

-- 
Wes Groleau
http://freepages.rootsweb.com/~wgroleau
_______________________________________________



^ permalink raw reply	[relevance 4%]

* I'm baffled...
@ 2001-10-30 22:16  4% Wes Groleau
  0 siblings, 0 replies; 132+ results
From: Wes Groleau @ 2001-10-30 22:16 UTC (permalink / raw)



Probably something simple, but I don't see it ....

I don't think it's a compiler bug because
I get the same error from Apex that I get from GNAT.

But how can I get a constraint_error on line 166
of ada.strings.maps?  That line is:
   Identity : constant Character_Mapping :=

I can't get either debugger to let me examine things
in the run-time.

Code excerpt:

   package ASF renames Ada.Strings.Fixed;
   package AS renames Ada.Strings;

   function Position_Of (Pattern : String) return Index is

      Result : Index := 47;
      -- just to make it any old legal value

      Checkpoint : Character := 'A';

   begin
      Checkpoint := 'B';
      Result := ASF.Index
                (Source  => Word_List (Current_Index + 1 ..
Word_List'Last),
                 Pattern => Pattern,
                 Going   => AS.Forward );
      Checkpoint := 'C';
      
      if Result /= 0 then
      Checkpoint := 'D';
         return Result;
      else
      Checkpoint := 'E';
         return ASF.Index
                (Source  => Word_List ( Word_List'First .. Current_Index
- 1),
                 Pattern => Pattern,
                 Going   => AS.Backward );
      Checkpoint := 'F';
      end if;
      Checkpoint := 'G';

   exception
      when E : others =>
        Ada.Text_IO.Put_Line (Ada.Exceptions.Exception_Information(E));
        Ada.Text_IO.Put_Line ("Checkpoint    => " & Checkpoint);
        Ada.Text_IO.Put_Line ("Context       => " & Word_List
(Current_Index - 10 .. Current_Index + 10) );
        Ada.Text_IO.Put_Line ("Pattern       => " & Pattern);
        Ada.Text_IO.Put_Line ("Current_Index => " & Integer'Image
(Current_Index));
        Ada.Text_IO.Put_Line ("Result        => " & Integer'Image
(Result));

      raise;

   end Position_Of;

Typical error output:

Exception name: CONSTRAINT_ERROR
Message: a-strmap.ads:166

Checkpoint    => B
Context       => addenda addendum adhe
Pattern       =>  pri
Current_Index =>  117947
Result        =>  47

(Word_List is a BIG string)

-- 
Wes Groleau
http://freepages.rootsweb.com/~wgroleau



^ permalink raw reply	[relevance 4%]

* Re: avl tree - booch components
    2001-09-10 21:52  5% ` Jeffrey D. Cherry
@ 2001-09-10 21:53  5% ` Jeffrey D. Cherry
  1 sibling, 0 replies; 132+ results
From: Jeffrey D. Cherry @ 2001-09-10 21:53 UTC (permalink / raw)


I once created the following package and driver program for a colleague.
It was derived from a much larger project where we used an AVL tree as 
part of a symbol table for a FORTRAN parser.  It compiles with GNAT v3.13p
under Windows 2000 and the August 19, 2001 version of the Booch components.
Though comments are somewhat sparse, there is some explanation regarding
instantiating the AVL tree.  Hope this helps.
-- 
Regards,
Jeffrey D. Cherry
Senior IV&V Analyst
Logicon Operations and Services
Logicon Inc.
a Northrop Grumman company



-- This is a simple package to store "keywords" and an associated data
-- item as an abstract data object.  We'll refer to this abstract data
-- object simply as the keyword container.

package Keyword_Manager is

   -- This is a dummy type so we can associate some kind of data with
   -- a key field.  The dummy type can, of course, be very complex if
   -- it is appropriate for the problem.  It could also be a generic
   -- parameter.  For that matter, the "key" type (strings in this
   -- example) could be a generic parameter as well.  I won't do that
   -- here since too many levels of generic instantiations will detract
   -- from what I'm trying to show.
   type ID_Type is (Unknown_ID, Known_ID, Another_ID, Yet_Another_ID);

-- Clear the keyword container of all (keyword,ID) pairs so that we
-- have an empty keyword container.
procedure Clear_Keywords;

-- Return true if the keyword container is empty and return false
-- if there are one or more (keyword,ID) pairs in the keyword container.
function Is_Empty return boolean;

-- Return the number of (keyword,ID) pairs in the keyword container.
function Number return natural;

-- Insert a keyword and its associated data into the keyword container.
-- If the keyword already exists, then the ignore the data.  (Normally
-- we would want to signal some kind of fault - perhaps via an exception.
-- However, we don't want to focus on error processing in this example.)
procedure Insert(
   Keyword : in string;
   ID      : in ID_Type);

-- Return true if the given keyword exists in the keyword container and
-- return false if it does not exist in the keyword container.
function Exists(Keyword : in string) return boolean;

-- Return the ID associated with the given keyword.  If the keyword
-- doesn't exist in the keyword container, then Unknown_ID is returned.
-- (Again, this should probably raise an exception but we're not
-- focusing on error processing.)
function Identify(Keyword : in string) return ID_Type;

-- Write the contents of the keyword container to standard output.
-- Normally we would want to make this ability much more flexible,
-- but we make another concession for a simple example.
procedure Put_Keywords;

end Keyword_Manager;


with Ada.Strings.Unbounded;             use Ada.Strings.Unbounded;
with Ada.Strings.Maps.Constants;

with BC.Containers.Trees.AVL.Print;
with BC.Support.Unmanaged_Storage;

package body Keyword_Manager is

   -- A node for the keyword table.  This is the information stored in
   -- the AVL tree.  We use unbounded strings since we don't know the
   -- length of our key strings.  If we did, we could use the bounded
   -- form from Ada.Strings.Bounded.
   type Keyword_Node is
      record
         Keyword : Unbounded_String := Null_Unbounded_String;
         ID      : ID_Type          := Unknown_ID;
      end record;

   -- Eventually, we'll need some kind of storage management for the
   -- Keyword_Node structures and the tree that stores the data.  For
   -- this example, we don't care too much about storage issues, so we'll
   -- use the default unmanaged storage provided by the Booch components.
   subtype Tree_Storage_Pool is BC.Support.Unmanaged_Storage.Pool;
   Tree_Storage : Tree_Storage_Pool;

-- Equality function used to identify equivalent nodes in the AVL tree.
-- Notice that the test is case insensative.
function Same_Keyword(Left, Right : in Keyword_Node) return boolean is
   use Ada.Strings.Maps.Constants;
begin -- Same_Keyword
   return Translate(Left.Keyword, Lower_Case_Map) =
         Translate(Right.Keyword, Lower_Case_Map);
end Same_Keyword;

-- Ordering function used to order nodes in the AVL tree.  Notice that
-- the nodes are in reverse alphabetical order and are case insensative.
function Is_Before(Left, Right : in Keyword_Node) return boolean is
   use Ada.Strings.Maps.Constants;
begin -- Is_Before
   return Translate(Left.Keyword, Lower_Case_Map) >
         Translate(Right.Keyword, Lower_Case_Map);
end Is_Before;


-- First create an abstract container that can hold our Keyword_Nodes and
-- can test for two identical Keyword_Nodes.
package Keyword_Containers is
   new BC.Containers(Item => Keyword_Node, "=" => Same_Keyword);

-- Since an abstract tree is just another form of an abstract container,
-- we create an abstract container that uses an abstract tree structure.
-- No new information is required to be given to the abstract tree
-- container and so this is just a simple instantiation built off our
-- previous container.
package Keyword_Container_Trees is new Keyword_Containers.Trees;

-- Now we must define a substantial form for the abstract tree container.
-- This is where we decide to use an AVL form of a tree rather than some
-- other form (e.g., binary or multiway).  Since a tree stores data in
-- an ordered fashion, we must tell the AVL tree how to order our data.
-- This is done with the ordering function we defined above (function
-- Is_Before).  This will also be our concrete package that must deal
-- with both allocation and deallocation of memory resources for the
-- tree nodes.
package Keyword_Trees is
   new Keyword_Container_Trees.AVL(
      "<"             => Is_Before,
      Storage_Manager => Tree_Storage_Pool,
      Storage         => Tree_Storage);

   -- Okay, we can now define an object that will contain our Keyword_Nodes.
   -- It is a container that uses an AVL tree structure to hold the data.
   Keyword_Table : Keyword_Trees.AVL_Tree;


procedure Clear_Keywords is
begin -- Clear_Keywords
   Keyword_Trees.Clear(Keyword_Table);
end Clear_Keywords;


function Is_Empty return boolean is
begin -- Is_Empty
   return Keyword_Trees.Is_Null(Keyword_Table);
end Is_Empty;


function Number return natural is
begin -- Number
   return Keyword_Trees.Extent(Keyword_Table);
end Number;


procedure Insert(
   Keyword : in string;
   ID      : in ID_Type) is

   Keyword_Added : boolean;

begin -- Insert
   Keyword_Trees.Insert(Keyword_Table,
         Keyword_Node'(To_Unbounded_String(Keyword), ID),
         Keyword_Added);
end Insert;


function Exists(Keyword : in string) return boolean is
begin -- Exists
   return Keyword_Trees.Is_Member(Keyword_Table,
         Keyword_Node'(To_Unbounded_String(Keyword), Unknown_ID));
end Exists;


function Identify(Keyword : in string) return ID_Type is

   ID    : ID_Type := Unknown_ID;
   Found : boolean;

procedure Get_ID(Item : in out Keyword_Node) is
begin -- Get_ID
   ID := Item.ID;
end Get_ID;

procedure Find_Node is new Keyword_Trees.Access_Actual_Item(Get_ID);

begin -- Identify
   Find_Node(Keyword_Table,
         Keyword_Node'(To_Unbounded_String(Keyword), Unknown_ID),
         Found);
   return ID;
end Identify;


procedure Put_Keywords is

function Keyword_Image(Item : in Keyword_Node) return string is
begin -- Keyword_Image
   return "(" & To_String(Item.Keyword) & "," & ID_Type'image(Item.ID) & ")";
end Keyword_Image;

procedure Put_Tree is new Keyword_Trees.Print(Keyword_Image);

begin -- Put_Keywords
   Put_Tree(Keyword_Table);
end Put_Keywords;

end Keyword_Manager;


with Ada.Command_Line;
with Ada.Text_IO;                       use Ada.Text_IO;
with Ada.Strings.Fixed;                 use Ada.Strings.Fixed;
with Ada.Strings.Maps.Constants;        use Ada.Strings.Maps.Constants;

with Keyword_Manager;                   use Keyword_Manager;

procedure KM_Test is

   Keyword_File : File_Type;
   Buffer       : string(1..1024);
   Last         : natural;
   i, j         : natural;
   ID           : ID_Type := Known_ID;

begin -- KM_Test
   if Ada.Command_Line.Argument_Count = 1 then
      Open(Keyword_File, In_File, Ada.Command_Line.Argument(1));
      Clear_Keywords;

      while not End_Of_File(Keyword_File) loop
         Get_Line(Keyword_File, Buffer, Last);
         if Last in Buffer'range then
            i := Buffer'first;
            loop
               Find_Token(Buffer(i..Last), Letter_Set, Ada.Strings.Inside, i,
j);
               exit when j = 0;
               Insert(Buffer(i..j), ID);
               if ID = Yet_Another_ID then
                  ID := Known_ID;
               else
                  ID := ID_Type'succ(ID);
               end if;
               i := natural'succ(j);
               exit when i > Last;
            end loop;
         end if;
      end loop;
      Close(Keyword_File);

      if Is_Empty then
         Put_Line("Keyword container is empty.");

      else
         Put_Line("There are" & natural'image(Number) &
               " items in the keyword container.");
         New_Line(2);
         Put_Line("Contents of the keyword container are as follows:");
         Put_Keywords;
         New_Line(4);

         loop
            Put("Enter keyword to look up: ");
            Get_Line(Buffer, Last);
            exit when Last not in Buffer'range;
            if Exists(Buffer(1..Last)) then
               Put_Line("""" & Buffer(1..Last) &
                     """ is in the keyword container and its ID is " &
                     ID_Type'image(Identify(Buffer(1..Last))) & ".");
            else
               Put_Line("""" & Buffer(1..Last) &
                     """ does not exist in the keyword container!");
            end if;
         end loop;
      end if;
   end if;
end KM_Test;



^ permalink raw reply	[relevance 5%]

* Re: avl tree - booch components
  @ 2001-09-10 21:52  5% ` Jeffrey D. Cherry
  2001-09-10 21:53  5% ` Jeffrey D. Cherry
  1 sibling, 0 replies; 132+ results
From: Jeffrey D. Cherry @ 2001-09-10 21:52 UTC (permalink / raw)


I once created the following package and driver program for a colleague.
It was derived from a much larger project where we used an AVL tree as 
part of a symbol table for a FORTRAN parser.  It compiles with GNAT v3.13p
under Windows 2000 and the August 19, 2001 version of the Booch components.
Though comments are somewhat sparse, there is some explanation regarding
instantiating the AVL tree.  Hope this helps.
-- 
Regards,
Jeffrey D. Cherry
Senior IV&V Analyst
Logicon Operations and Services
Logicon Inc.
a Northrop Grumman company



-- This is a simple package to store "keywords" and an associated data
-- item as an abstract data object.  We'll refer to this abstract data
-- object simply as the keyword container.

package Keyword_Manager is

   -- This is a dummy type so we can associate some kind of data with
   -- a key field.  The dummy type can, of course, be very complex if
   -- it is appropriate for the problem.  It could also be a generic
   -- parameter.  For that matter, the "key" type (strings in this
   -- example) could be a generic parameter as well.  I won't do that
   -- here since too many levels of generic instantiations will detract
   -- from what I'm trying to show.
   type ID_Type is (Unknown_ID, Known_ID, Another_ID, Yet_Another_ID);

-- Clear the keyword container of all (keyword,ID) pairs so that we
-- have an empty keyword container.
procedure Clear_Keywords;

-- Return true if the keyword container is empty and return false
-- if there are one or more (keyword,ID) pairs in the keyword container.
function Is_Empty return boolean;

-- Return the number of (keyword,ID) pairs in the keyword container.
function Number return natural;

-- Insert a keyword and its associated data into the keyword container.
-- If the keyword already exists, then the ignore the data.  (Normally
-- we would want to signal some kind of fault - perhaps via an exception.
-- However, we don't want to focus on error processing in this example.)
procedure Insert(
   Keyword : in string;
   ID      : in ID_Type);

-- Return true if the given keyword exists in the keyword container and
-- return false if it does not exist in the keyword container.
function Exists(Keyword : in string) return boolean;

-- Return the ID associated with the given keyword.  If the keyword
-- doesn't exist in the keyword container, then Unknown_ID is returned.
-- (Again, this should probably raise an exception but we're not
-- focusing on error processing.)
function Identify(Keyword : in string) return ID_Type;

-- Write the contents of the keyword container to standard output.
-- Normally we would want to make this ability much more flexible,
-- but we make another concession for a simple example.
procedure Put_Keywords;

end Keyword_Manager;


with Ada.Strings.Unbounded;             use Ada.Strings.Unbounded;
with Ada.Strings.Maps.Constants;

with BC.Containers.Trees.AVL.Print;
with BC.Support.Unmanaged_Storage;

package body Keyword_Manager is

   -- A node for the keyword table.  This is the information stored in
   -- the AVL tree.  We use unbounded strings since we don't know the
   -- length of our key strings.  If we did, we could use the bounded
   -- form from Ada.Strings.Bounded.
   type Keyword_Node is
      record
         Keyword : Unbounded_String := Null_Unbounded_String;
         ID      : ID_Type          := Unknown_ID;
      end record;

   -- Eventually, we'll need some kind of storage management for the
   -- Keyword_Node structures and the tree that stores the data.  For
   -- this example, we don't care too much about storage issues, so we'll
   -- use the default unmanaged storage provided by the Booch components.
   subtype Tree_Storage_Pool is BC.Support.Unmanaged_Storage.Pool;
   Tree_Storage : Tree_Storage_Pool;

-- Equality function used to identify equivalent nodes in the AVL tree.
-- Notice that the test is case insensative.
function Same_Keyword(Left, Right : in Keyword_Node) return boolean is
   use Ada.Strings.Maps.Constants;
begin -- Same_Keyword
   return Translate(Left.Keyword, Lower_Case_Map) =
         Translate(Right.Keyword, Lower_Case_Map);
end Same_Keyword;

-- Ordering function used to order nodes in the AVL tree.  Notice that
-- the nodes are in reverse alphabetical order and are case insensative.
function Is_Before(Left, Right : in Keyword_Node) return boolean is
   use Ada.Strings.Maps.Constants;
begin -- Is_Before
   return Translate(Left.Keyword, Lower_Case_Map) >
         Translate(Right.Keyword, Lower_Case_Map);
end Is_Before;


-- First create an abstract container that can hold our Keyword_Nodes and
-- can test for two identical Keyword_Nodes.
package Keyword_Containers is
   new BC.Containers(Item => Keyword_Node, "=" => Same_Keyword);

-- Since an abstract tree is just another form of an abstract container,
-- we create an abstract container that uses an abstract tree structure.
-- No new information is required to be given to the abstract tree
-- container and so this is just a simple instantiation built off our
-- previous container.
package Keyword_Container_Trees is new Keyword_Containers.Trees;

-- Now we must define a substantial form for the abstract tree container.
-- This is where we decide to use an AVL form of a tree rather than some
-- other form (e.g., binary or multiway).  Since a tree stores data in
-- an ordered fashion, we must tell the AVL tree how to order our data.
-- This is done with the ordering function we defined above (function
-- Is_Before).  This will also be our concrete package that must deal
-- with both allocation and deallocation of memory resources for the
-- tree nodes.
package Keyword_Trees is
   new Keyword_Container_Trees.AVL(
      "<"             => Is_Before,
      Storage_Manager => Tree_Storage_Pool,
      Storage         => Tree_Storage);

   -- Okay, we can now define an object that will contain our Keyword_Nodes.
   -- It is a container that uses an AVL tree structure to hold the data.
   Keyword_Table : Keyword_Trees.AVL_Tree;


procedure Clear_Keywords is
begin -- Clear_Keywords
   Keyword_Trees.Clear(Keyword_Table);
end Clear_Keywords;


function Is_Empty return boolean is
begin -- Is_Empty
   return Keyword_Trees.Is_Null(Keyword_Table);
end Is_Empty;


function Number return natural is
begin -- Number
   return Keyword_Trees.Extent(Keyword_Table);
end Number;


procedure Insert(
   Keyword : in string;
   ID      : in ID_Type) is

   Keyword_Added : boolean;

begin -- Insert
   Keyword_Trees.Insert(Keyword_Table,
         Keyword_Node'(To_Unbounded_String(Keyword), ID),
         Keyword_Added);
end Insert;


function Exists(Keyword : in string) return boolean is
begin -- Exists
   return Keyword_Trees.Is_Member(Keyword_Table,
         Keyword_Node'(To_Unbounded_String(Keyword), Unknown_ID));
end Exists;


function Identify(Keyword : in string) return ID_Type is

   ID    : ID_Type := Unknown_ID;
   Found : boolean;

procedure Get_ID(Item : in out Keyword_Node) is
begin -- Get_ID
   ID := Item.ID;
end Get_ID;

procedure Find_Node is new Keyword_Trees.Access_Actual_Item(Get_ID);

begin -- Identify
   Find_Node(Keyword_Table,
         Keyword_Node'(To_Unbounded_String(Keyword), Unknown_ID),
         Found);
   return ID;
end Identify;


procedure Put_Keywords is

function Keyword_Image(Item : in Keyword_Node) return string is
begin -- Keyword_Image
   return "(" & To_String(Item.Keyword) & "," & ID_Type'image(Item.ID) & ")";
end Keyword_Image;

procedure Put_Tree is new Keyword_Trees.Print(Keyword_Image);

begin -- Put_Keywords
   Put_Tree(Keyword_Table);
end Put_Keywords;

end Keyword_Manager;


with Ada.Command_Line;
with Ada.Text_IO;                       use Ada.Text_IO;
with Ada.Strings.Fixed;                 use Ada.Strings.Fixed;
with Ada.Strings.Maps.Constants;        use Ada.Strings.Maps.Constants;

with Keyword_Manager;                   use Keyword_Manager;

procedure KM_Test is

   Keyword_File : File_Type;
   Buffer       : string(1..1024);
   Last         : natural;
   i, j         : natural;
   ID           : ID_Type := Known_ID;

begin -- KM_Test
   if Ada.Command_Line.Argument_Count = 1 then
      Open(Keyword_File, In_File, Ada.Command_Line.Argument(1));
      Clear_Keywords;

      while not End_Of_File(Keyword_File) loop
         Get_Line(Keyword_File, Buffer, Last);
         if Last in Buffer'range then
            i := Buffer'first;
            loop
               Find_Token(Buffer(i..Last), Letter_Set, Ada.Strings.Inside, i,
j);
               exit when j = 0;
               Insert(Buffer(i..j), ID);
               if ID = Yet_Another_ID then
                  ID := Known_ID;
               else
                  ID := ID_Type'succ(ID);
               end if;
               i := natural'succ(j);
               exit when i > Last;
            end loop;
         end if;
      end loop;
      Close(Keyword_File);

      if Is_Empty then
         Put_Line("Keyword container is empty.");

      else
         Put_Line("There are" & natural'image(Number) &
               " items in the keyword container.");
         New_Line(2);
         Put_Line("Contents of the keyword container are as follows:");
         Put_Keywords;
         New_Line(4);

         loop
            Put("Enter keyword to look up: ");
            Get_Line(Buffer, Last);
            exit when Last not in Buffer'range;
            if Exists(Buffer(1..Last)) then
               Put_Line("""" & Buffer(1..Last) &
                     """ is in the keyword container and its ID is " &
                     ID_Type'image(Identify(Buffer(1..Last))) & ".");
            else
               Put_Line("""" & Buffer(1..Last) &
                     """ does not exist in the keyword container!");
            end if;
         end loop;
      end if;
   end if;
end KM_Test;



^ permalink raw reply	[relevance 5%]

* Re: String manupulation
  @ 2001-08-23 12:46  6%           ` David C. Hoos
  0 siblings, 0 replies; 132+ results
From: David C. Hoos @ 2001-08-23 12:46 UTC (permalink / raw)
  To: comp.lang.ada; +Cc: Reinert.Korsnes

I personally use the following definition:

   Whitespace : constant Ada.Strings.Maps.Character_Set :=
     Ada.Strings.Maps.To_Set
     (Ada.Strings.Maps.Character_Range'((Character'Val (0), ' ')));

----- Original Message ----- 
From: "Reinert Korsnes" <Reinert.Korsnes@ffi.no>
Newsgroups: comp.lang.ada
To: <comp.lang.ada@ada.eu.org>
Sent: Thursday, August 23, 2001 3:21 AM
Subject: Re: String manupulation


> David C. Hoos wrote:
> 
> > Some additional style comments:
> > 
> > 1. One might wish to extend the "Space" object
> >     to be "Whitespace" with the appropriate set of
> >     characters, in case one is reading a file with
> >     tabs or other "whitespace" characters.
> > 
> 
> How do I define Whitespace ?
> I look at Ada.Characters.Latin-1  (find HT etc).
> Should I compose my own definition or is there something build-in
> and which I have not discovered ?
> 
> reinert
> 
> ...snip...
> 
> -- 
> http://home.chello.no/~rkorsnes
> _______________________________________________
> comp.lang.ada mailing list
> comp.lang.ada@ada.eu.org
> http://ada.eu.org/mailman/listinfo/comp.lang.ada
> 




^ permalink raw reply	[relevance 6%]

* String manupulation (again) - free software
@ 2001-08-23 12:15  6% Reinert Korsnes
  0 siblings, 0 replies; 132+ results
From: Reinert Korsnes @ 2001-08-23 12:15 UTC (permalink / raw)


Hi,

Enclosed is a simple package to split character strings
into substrings consisting of continuous sequences of letters or
groups of characters bounded by Quotation (so "abc def, ghijk"
is one "word").  Not that this may be so interesting, but it could
be useful for me get this improved/criticized.  At least I can
learn some Ada from this.....

Below is also a test program for this package.
(package spec not included).

reinert


-----------------------------------------------

-- Author: R.Korsnes, with help from comp.lang.ada :-)  23 August 2001.

with Ada.Text_IO;
use  Ada.Text_IO;
with Ada.Integer_Text_IO,Ada.Strings.Fixed,Ada.Strings.Maps;
with Ada.Characters.Latin_1;
use  Ada.Characters.Latin_1;
package body Rsplit is
   use  Ada.Integer_Text_IO;
   use  Ada.Strings,Ada.Strings.Fixed,Ada.Strings.Maps;

   Set : constant Character_Set := To_Set(" ," & HT); 

   function Number_Of_Words(FS : String) return Integer is
      N     : Natural := 0;
      First : Natural := FS'First;
      Last  : Natural;
   begin
      loop
         Find_Token(Source => FS(First..FS'Last),
                    Set    => Set,
                    Test   => Ada.Strings.Outside,
                    First  => First,
                    Last   => Last);
         exit when Last = 0;
         if FS(First) = Quotation then
            Last  := Index(Source => FS(First+1..FS'Last),
                              Set => To_Set(Quotation));
         end if;
         N := N + 1;
         First := Last + 1;
      end loop; 
      Return N;
   end Number_Of_Words;

   function Word(FS : String;Word_Number : Integer) return String is
      N     : Natural := 0;
      First : Natural := FS'First;
      Last  : Natural;
   begin
      loop
         Find_Token(Source => FS(First..FS'Last),
                    Set    => Set,
                    Test   => Ada.Strings.Outside,
                    First  => First,
                    Last   => Last);
         exit when Last = 0;
         if FS(First) = Quotation then
            Last  := Index(Source => FS(First+1..FS'Last),
                              Set => To_Set(Quotation));
         end if;
         N := N + 1;
         if Word_Number = N then
            return FS(First .. Last);
         end if;
         First := Last+1;
      end loop; 
      Return "";
   end Word;

end rsplit;
----------------------------

Test program:

with rsplit;
with Text_IO,Ada.Strings.Fixed,Ada.Strings.Maps,Ada.Characters.Latin_1;
with Ada.Integer_Text_IO;
 
use  Text_IO,Ada.Strings,Ada.Strings.Fixed,Ada.Strings.Maps;
use  Ada.Characters.Latin_1;
use  Ada.Integer_Text_IO;
 
procedure rstring is
   FS : constant String :=
        "  This " & Quotation & "   is a test"
                  & Quotation & " to " & Quotation &
                 "split a string" & Quotation & " ";
 
   C1 : constant String :=         "123456789012345678901234567890123456";
 
begin
   Put(C1);New_Line;
   Put(FS);New_Line;
 
     for I in 1 .. Rsplit.Number_Of_Words(FS) loop
      New_Line;
      Put(I); Put(" ");Put(" "); Put(Rsplit.Word(FS,I));
     end loop;
end rstring;

-- 
http://home.chello.no/~rkorsnes



^ permalink raw reply	[relevance 6%]

* Re: String manupulation
  2001-08-22 15:53  6%     ` Ted Dennison
@ 2001-08-22 16:23  4%       ` David C. Hoos
    0 siblings, 1 reply; 132+ results
From: David C. Hoos @ 2001-08-22 16:23 UTC (permalink / raw)
  To: comp.lang.ada; +Cc: Ted Dennison, Reinert.Korsnes

Some additional style comments:

1. One might wish to extend the "Space" object
    to be "Whitespace" with the appropriate set of
    characters, in case one is reading a file with
    tabs or other "whitespace" characters.

2.  The use of a construct like FS'Length would
     better be replaced with FS'Last to cover cases like
     the string being parsed is an input parameter to the
     subprogram, and the caller calls with a slice not
     starting with index 1.

----- Original Message -----
From: "Ted Dennison" <dennison@telepath.com>
Newsgroups: comp.lang.ada
To: <comp.lang.ada@ada.eu.org>
Sent: Wednesday, August 22, 2001 10:53 AM
Subject: Re: String manupulation


> In article <9lvq0p$cpm$1@snipp.uninett.no>, Reinert Korsnes says...
> >
> >Thanks to all of you.  Is this the (dirty ?) way to do it (?) :
>
> Some style comments:
>
> o  Anything that never changes after the declaration should be declared
> "constant".
>
> o  There's already an instantiation of Integer_IO for Integer. Its
> Ada.Integer_Text_IO.
>
> o Unless it won't work for some reason, I generally prefer to use 'Image
rather
> than a numeric Text_IO instantiation.
>
> o You don't need to "with" a package if you already "with" one of its
children.
>
> o Except in extreme quick-n-dirty code, I always specify the parameter
names in
> multi-parameter subprogram calls.
>
> o (Contraversial) I prefer to aviod the "use" clause.
>
> o There's no indication where the "1" you initialize those variables to
comes
> from or why its there. Instead, only initialize the one(s) you need to,
and do
> it from the array it is using to index through.
>
> Also, while transforming that appropriately, I noticed that you have a bug
where
> it doesn't handle a final substring of length 1 properly. That's the kind
of
> thing you are more apt to notice the more closely you tie your indices to
your
> array.
>
> Also, Find_Token returns 0 for Last when no more spaces are found. If you
supply
> a string that doesn't end in a space, your code will loop endlessly. The
> *proper* way to terminate your "Find_Token" based loop is to terminate
when no
> further token is found (Last = 0).
>
> Given all that, I'd transform it to:
> ------------------------
> with Ada.Text_IO;
> with Ada.Strings.Fixed;
> with Ada.Strings.Maps;
>
> procedure Rtest1 is
> FS    : constant String := " This is a test to split a string ";
> C1    : constant String := "123456789012345678901234";
> Space : constant Ada.Strings.Maps.Character_Set :=
Ada.Strings.Maps.To_Set(" ");
>
> First : Natural := Fs'First;
> Last  : Natural;
> begin
> Ada.Text_IO.Put_Line (C1);
> Ada.Text_IO.Put_Line (FS);
>
> loop
> Ada.Strings.Fixed.Find_Token
> (Source => FS(First..FS'Length),
> Set    => Space,
> Test   => Ada.Strings.Outside,
> First  => First,
> Last   => Last
> );
>
> exit when Last = 0;
>
> Ada.Text_IO.Put_Line
> (Integer'Image(First) & Integer'Image(Last) & " " & Fs (First..Last));
>
> First := Last + 1;
> end loop;
> end Rtest1;
> -------------
>
> To satify those who don't agree with the "no use" bit, I'll also include a
> version with "use"s. Obviously *I* don't think it looks better, but some
here
> surely will:
>
> -------------
> with Ada.Text_IO;
> with Ada.Strings.Fixed;
> with Ada.Strings.Maps;
>
> use Ada.Text_IO;
> use Ada.Strings.Fixed;
> use Ada.Strings.Maps;
>
> procedure Rtest1 is
> FS    : constant String := " This is a test to split a string ";
> C1    : constant String := "123456789012345678901234";
> Space : constant Character_Set := To_Set(" ");
>
> First : Natural := Fs'First;
> Last  : Natural;
> begin
> Put_Line (C1);
> Put_Line (FS);
>
> loop
> Find_Token
> (Source => FS(First..FS'Length),
> Set    => Space,
> Test   => Ada.Strings.Outside,
> First  => First,
> Last   => Last
> );
>
> exit when Last = 0;
>
> Put_Line
> (Integer'Image(First) & Integer'Image(Last) & " " & Fs (First..Last));
>
> First := Last + 1;
> end loop;
> end Rtest1;
> -------------
>
> ---
> T.E.D.    homepage   - http://www.telepath.com/dennison/Ted/TED.html
>           home email - mailto:dennison@telepath.com
> _______________________________________________
> comp.lang.ada mailing list
> comp.lang.ada@ada.eu.org
> http://ada.eu.org/mailman/listinfo/comp.lang.ada
>




^ permalink raw reply	[relevance 4%]

* Re: String manupulation
  2001-08-22  8:15  6%   ` Reinert Korsnes
@ 2001-08-22 15:53  6%     ` Ted Dennison
  2001-08-22 16:23  4%       ` David C. Hoos
  0 siblings, 1 reply; 132+ results
From: Ted Dennison @ 2001-08-22 15:53 UTC (permalink / raw)


In article <9lvq0p$cpm$1@snipp.uninett.no>, Reinert Korsnes says...
>
>Thanks to all of you.  Is this the (dirty ?) way to do it (?) :

Some style comments:

o  Anything that never changes after the declaration should be declared
"constant".

o  There's already an instantiation of Integer_IO for Integer. Its
Ada.Integer_Text_IO.

o Unless it won't work for some reason, I generally prefer to use 'Image rather
than a numeric Text_IO instantiation.

o You don't need to "with" a package if you already "with" one of its children.

o Except in extreme quick-n-dirty code, I always specify the parameter names in
multi-parameter subprogram calls.

o (Contraversial) I prefer to aviod the "use" clause.

o There's no indication where the "1" you initialize those variables to comes
from or why its there. Instead, only initialize the one(s) you need to, and do
it from the array it is using to index through.

Also, while transforming that appropriately, I noticed that you have a bug where
it doesn't handle a final substring of length 1 properly. That's the kind of
thing you are more apt to notice the more closely you tie your indices to your
array. 

Also, Find_Token returns 0 for Last when no more spaces are found. If you supply
a string that doesn't end in a space, your code will loop endlessly. The
*proper* way to terminate your "Find_Token" based loop is to terminate when no
further token is found (Last = 0).

Given all that, I'd transform it to:
------------------------
with Ada.Text_IO;
with Ada.Strings.Fixed;
with Ada.Strings.Maps;

procedure Rtest1 is
FS    : constant String := " This is a test to split a string ";
C1    : constant String := "123456789012345678901234";
Space : constant Ada.Strings.Maps.Character_Set := Ada.Strings.Maps.To_Set(" ");

First : Natural := Fs'First;
Last  : Natural;
begin
Ada.Text_IO.Put_Line (C1);
Ada.Text_IO.Put_Line (FS);

loop
Ada.Strings.Fixed.Find_Token
(Source => FS(First..FS'Length),
Set    => Space,
Test   => Ada.Strings.Outside,
First  => First,
Last   => Last
);

exit when Last = 0;

Ada.Text_IO.Put_Line
(Integer'Image(First) & Integer'Image(Last) & " " & Fs (First..Last));

First := Last + 1;
end loop;
end Rtest1;
-------------

To satify those who don't agree with the "no use" bit, I'll also include a
version with "use"s. Obviously *I* don't think it looks better, but some here
surely will:

-------------
with Ada.Text_IO;
with Ada.Strings.Fixed;
with Ada.Strings.Maps;

use Ada.Text_IO;
use Ada.Strings.Fixed;
use Ada.Strings.Maps;

procedure Rtest1 is
FS    : constant String := " This is a test to split a string ";
C1    : constant String := "123456789012345678901234";
Space : constant Character_Set := To_Set(" ");

First : Natural := Fs'First;
Last  : Natural;
begin
Put_Line (C1);
Put_Line (FS);

loop
Find_Token
(Source => FS(First..FS'Length),
Set    => Space,
Test   => Ada.Strings.Outside,
First  => First,
Last   => Last
);

exit when Last = 0;

Put_Line
(Integer'Image(First) & Integer'Image(Last) & " " & Fs (First..Last));

First := Last + 1;
end loop;
end Rtest1;
-------------

---
T.E.D.    homepage   - http://www.telepath.com/dennison/Ted/TED.html
          home email - mailto:dennison@telepath.com



^ permalink raw reply	[relevance 6%]

* Re: String manupulation
  @ 2001-08-22  8:15  6%   ` Reinert Korsnes
  2001-08-22 15:53  6%     ` Ted Dennison
  0 siblings, 1 reply; 132+ results
From: Reinert Korsnes @ 2001-08-22  8:15 UTC (permalink / raw)


Thanks to all of you.  Is this the (dirty ?) way to do it (?) :

-----------------------------------------------
with Text_IO,Ada.Strings,Ada.Strings.Fixed,Ada.Strings.Maps;
use  Text_IO,Ada.Strings,Ada.Strings.Fixed,Ada.Strings.Maps;
procedure Rtest1 is
   package Int_Io is new Text_IO.Integer_Io (Integer);
   use Int_Io;
   I,J : Integer := 1;
   FS : String := " This is a test to split a string ";
   C1 : String := "123456789012345678901234";
   Set : Character_Set := To_Set(" ");
begin
   Put(C1);New_Line;
   Put(FS);New_Line;
   while I < FS'Length loop
      Find_Token(FS(I..FS'Length),Set,Outside,I,J);
      Put(I);Put(J); Put(" ");Put(FS(I..J));New_Line;
      I := J+1;
   end loop;
end Rtest1;
-----------------------------------------------

Randy Brukardt wrote:

> Reinert Korsnes wrote in message <9lt2pe$lrm$1@snipp.uninett.no>...
>>Hi,
>>
>>I just wondered if there is a simple/direct way (in Ada) to split
>>a string with words (for example "abc    defg  2.56  hijklm")
>>into stings each containing one word ("abc", "defg", "2.56" and
> "hijklm") ?
> 
> Look at Ada.Strings.Fixed.Find_Token (see RM A.4.3(68):
> http://www.adaic.com/standards/95lrm/html/RM-A-4-3.html)
> 
> There are versions of this in Ada.Strings.Bounded and
> Ada.Strings.Unbounded as well.
> 
>                 Randy Brukardt.
> 
> 
> 
> 
> 

-- 
http://home.chello.no/~rkorsnes



^ permalink raw reply	[relevance 6%]

* Re: Regex and/or LaTeX
    2001-02-26 11:41  6%     ` Lutz Donnerhacke
@ 2001-02-26 11:48  6%     ` Lutz Donnerhacke
  1 sibling, 0 replies; 132+ results
From: Lutz Donnerhacke @ 2001-02-26 11:48 UTC (permalink / raw)


* Adrian Knoth wrote:
>   procedure texstring (ausdruck : in out ustring) is
>      tmp : string := To_string(ausdruck);
>      hs : ustring := To_Ustring("");
>   begin
>      ausdruck := To_ustring("");
>      for I in tmp'range loop
>         case tmp(I) is
>            when '&' => hs := To_Ustring("\&");
>            when '%' => hs := To_Ustring("\%");
>            when others => hs := To_Ustring(tmp(I) & "");
>         end case;
>         ausdruck := ausdruck & hs;
>      end loop;
>   end texstring;

This seems to be Perl Style.

function texify (ausdruck      : String;
                 escape_char   : Character := '\\';
                 to_be_escaped : String    := "\\{}[]%^_") return String is
   pattern : Ada.Strings.Maps.Character_Set :=
             Ada.Strings.Maps.To_Set (to_be_escaped);
   i       : Ada.Strings.Fixed.Index (ausdruck, pattern);
begin
   if i = 0 then
      return ausdruck;
   elsif i = ausdruck'Last then
      return ausdruck (ausdruck'First .. i - 1) & escape_char & ausdruck (i);
   else
      return ausdruck (ausdruck'First .. i - 1) & escape_char & ausdruck (i) &
             texify (ausdruck (i + 1 .. ausdruck'Last),
                     escape_char, to_be_escaped);
   end if;
end texify;



^ permalink raw reply	[relevance 6%]

* Re: Regex and/or LaTeX
  @ 2001-02-26 11:41  6%     ` Lutz Donnerhacke
  2001-02-26 11:48  6%     ` Lutz Donnerhacke
  1 sibling, 0 replies; 132+ results
From: Lutz Donnerhacke @ 2001-02-26 11:41 UTC (permalink / raw)


* Adrian Knoth wrote:
>   procedure texstring (ausdruck : in out ustring) is
>      tmp : string := To_string(ausdruck);
>      hs : ustring := To_Ustring("");
>   begin
>      ausdruck := To_ustring("");
>      for I in tmp'range loop
>         case tmp(I) is
>            when '&' => hs := To_Ustring("\&");
>            when '%' => hs := To_Ustring("\%");
>            when others => hs := To_Ustring(tmp(I) & "");
>         end case;
>         ausdruck := ausdruck & hs;
>      end loop;
>   end texstring;

This seems to be Perl Style.

function texify (ausdruck      : String;
                 escape_char   : Character := '\\';
                 to_be_escaped : String    := "\\{}[]%^_") return String is
   pattern : Ada.Strings.Maps.Character_Set :=
             Ada.Strings.Maps.To_Set (to_be_escaped);
   pos     : Ada.Strings.Fixed.Index (ausdruck, pattern);
begin
   if pos = 0 then
      return ausdruck;
   elsif i = ausdruck'Last then
      return ausdruck (ausdruck'First .. i - 1) & escape_char & ausdruck (i);
   else
      return ausdruck (ausdruck'First .. i - 1) & escape_char & ausdruck (i) &
             texify (ausdruck (i + 1 .. ausdruck'Last),
                     escape_char, to_be_escaped);
   end if;
end texify;



^ permalink raw reply	[relevance 6%]

* CONTRAINT ERROR (was Re: parsing a string)
  2000-01-24  0:00  4%     ` Stephen Leake
@ 2000-01-26  0:00  0%       ` pumilia
  2000-01-26  0:00  0%         ` Roger Racine
  0 siblings, 1 reply; 132+ results
From: pumilia @ 2000-01-26  0:00 UTC (permalink / raw)


In article <uu2k3kszb.fsf@gsfc.nasa.gov>,
  Stephen Leake <Stephen.Leake@gsfc.nasa.gov> wrote:

> Index is a function, which must be assigned to a value, so this can't
> be the real source. Please include your _complete_ test program, so we
> can compile it ourselves, to help get a good answer.
>
> The default for Map should be fine. You can find out what else you
> might pass for Map in the package Ada.Strings.Maps.
>
> -- Stephe
>

Ok, i simplified my program, adjusted something thanks to David Hoos's
and
your useful comments and found a new error: CONSTRAINT_ERROR.

Here is my test procedure, aimed to converting an unbounded string
to string and then to parse the string:

-- str2_test --------------------------------------
with   ada.strings.unbounded;
use    ada.strings.unbounded;
with    ustrings;
use      ustrings;
with   text_io;
with   Ada.Integer_Text_IO;
use    text_io;
with ada.strings.fixed; use ada.strings.fixed;

with Ada.Integer_Text_IO;
use Ada.Integer_Text_IO;

procedure str2_test is

 output_file_string : unbounded_string ;
 output_file : string (1..25) ;
 pos1 : natural;

Begin

    get_line(output_file_string);

   put(" output:  "); put(output_file_string); put("<--"); new_line;
   output_file :=  to_string(output_file_string);
   put(" Output:  "); put(output_file); put("<--"); new_line;
   put(" index:  "); pos1 := Index(output_file,"xxx");
   put(pos1);
   new_line;

end str2_test;
-- str2_test --------------------------------------


While executing i get the error:

>   raised constraint_error : str2_test.adb:24

This is line 24:

  output_file :=  to_string(output_file_string);


Any help wil be appreciiated
thank you
Pol

- ustrings.ads ---------------------------------
-- Ideally this would be a child package of "Ada.Strings.Unbounded".

-- package Ustrings is
--   procedure Get_Line(Item : out Unbounded_String);
--   procedure Put(Item : in Unbounded_String);
--   procedure Put_Line(Item : in Unbounded_String);
-- end Ustrings;
--
-- Copyright (C) 1996 Ada Resource Association (ARA), Columbus, Ohio.
-- Author: David A. Wheeler
--

with Text_IO, Ada.Strings.Unbounded;
use  Text_IO, Ada.Strings.Unbounded;

package Ustrings is

  -- This package provides a simpler way to work with type
  -- Unbounded_String, since this type will be used very often.
  -- Most users will want to ALSO with "Ada.Strings.Unbounded".
  -- Ideally this would be a child package of "Ada.Strings.Unbounded".
  --

  -- This package provides the following simplifications:
  --  + Shortens the type name from "Unbounded_String" to "Ustring".
  --  + Creates shorter function names for To_Unbounded_String, i.e.
  --    To_Ustring(U) and U(S).  "U" is not a very readable name, but
  --    it's such a common operation that a short name seems appropriate
  --    (this function is needed every time a String constant is used).
  --    It also creates S(U) as the reverse of U(S).
  --  + Adds other subprograms, currently just "Swap".
  --  + Other packages can use this package to provide other
simplifications.

  subtype Ustring is Unbounded_String;

  function To_Ustring(Source : String)  return Unbounded_String
                                         renames To_Unbounded_String;
  function U(Source : String)           return Unbounded_String
                                         renames To_Unbounded_String;
  function S(Source : Unbounded_String) return String
                                         renames To_String;

  -- "Swap" is important for reuse in some other packages, so we'll
define it.

  procedure Swap(Left, Right : in out Unbounded_String);


  function Empty(S : Unbounded_String) return Boolean;
   -- returns True if Length(S)=0.
  pragma Inline(Empty);


  -- I/O Routines.
  procedure Get_Line(File : in File_Type; Item : out Unbounded_String);
  procedure Get_Line(Item : out Unbounded_String);

  procedure Put(File : in File_Type; Item : in Unbounded_String);
  procedure Put(Item : in Unbounded_String);

  procedure Put_Line(File : in File_Type; Item : in Unbounded_String);
  procedure Put_Line(Item : in Unbounded_String);

end Ustrings;

- ustrings.ads ---------------------------------



Sent via Deja.com http://www.deja.com/
Before you buy.




^ permalink raw reply	[relevance 0%]

* Re: CONTRAINT ERROR (was Re: parsing a string)
  2000-01-26  0:00  0%       ` CONTRAINT ERROR (was Re: parsing a string) pumilia
@ 2000-01-26  0:00  0%         ` Roger Racine
  0 siblings, 0 replies; 132+ results
From: Roger Racine @ 2000-01-26  0:00 UTC (permalink / raw)


On Wed, 26 Jan 2000 11:33:44 GMT, pumilia@est.it wrote:

>In article <uu2k3kszb.fsf@gsfc.nasa.gov>,
>  Stephen Leake <Stephen.Leake@gsfc.nasa.gov> wrote:
>
>> Index is a function, which must be assigned to a value, so this can't
>> be the real source. Please include your _complete_ test program, so we
>> can compile it ourselves, to help get a good answer.
>>
>> The default for Map should be fine. You can find out what else you
>> might pass for Map in the package Ada.Strings.Maps.
>>
>> -- Stephe
>>
>
>Ok, i simplified my program, adjusted something thanks to David Hoos's
>and
>your useful comments and found a new error: CONSTRAINT_ERROR.
>
>Here is my test procedure, aimed to converting an unbounded string
>to string and then to parse the string:
>
>-- str2_test --------------------------------------
>with   ada.strings.unbounded;
>use    ada.strings.unbounded;
>with    ustrings;
>use      ustrings;
>with   text_io;
>with   Ada.Integer_Text_IO;
>use    text_io;
>with ada.strings.fixed; use ada.strings.fixed;
>
>with Ada.Integer_Text_IO;
>use Ada.Integer_Text_IO;
>
>procedure str2_test is
>
> output_file_string : unbounded_string ;
> output_file : string (1..25) ;
> pos1 : natural;
>
>Begin
>
>    get_line(output_file_string);
>
>   put(" output:  "); put(output_file_string); put("<--"); new_line;
>   output_file :=  to_string(output_file_string);
>   put(" Output:  "); put(output_file); put("<--"); new_line;
>   put(" index:  "); pos1 := Index(output_file,"xxx");
>   put(pos1);
>   new_line;
>
>end str2_test;
>-- str2_test --------------------------------------
>
>
>While executing i get the error:
>
>>   raised constraint_error : str2_test.adb:24
>
>This is line 24:
>
>  output_file :=  to_string(output_file_string);
>
>
>Any help wil be appreciiated
>thank you
>Pol
>
>- ustrings.ads ---------------------------------
>-- Ideally this would be a child package of "Ada.Strings.Unbounded".
>
>-- package Ustrings is
>--   procedure Get_Line(Item : out Unbounded_String);
>--   procedure Put(Item : in Unbounded_String);
>--   procedure Put_Line(Item : in Unbounded_String);
>-- end Ustrings;
>--
>-- Copyright (C) 1996 Ada Resource Association (ARA), Columbus, Ohio.
>-- Author: David A. Wheeler
>--
>

The unbounded string Output_File_String can be of any length.  The
string Output_File is exactly 25 characters.  The following will help:

  Ulength : Natural;
...
   ULength := Length (Output_File_String);
   if ULength > Output_file'Length then
-- Do something to make sure bad input is caught

      raise Constraint_Error;  

   else

   Output_File(1 .. ULength) :=  to_string(output_file_string);
...
end if;

Roger Racine





^ permalink raw reply	[relevance 0%]

* Re: parsing a string
  @ 2000-01-24  0:00  4%     ` Stephen Leake
  2000-01-26  0:00  0%       ` CONTRAINT ERROR (was Re: parsing a string) pumilia
  0 siblings, 1 reply; 132+ results
From: Stephen Leake @ 2000-01-24  0:00 UTC (permalink / raw)


pumilia@est.it writes:

> In article <85q63n$ese$1@bgtnsc01.worldnet.att.net>,

> Thank you for help. i have found the function Index, defined as follows
> 
>      function Index (Source   : in String;
>                    Pattern  : in String;
>                    Going    : in Direction := Forward;
>                    Mapping  : in Maps.Character_Mapping
>                                 := Maps.Identity)
>       return Natural;
> 
> in package Ada.Strings.Fixed
> 
> I guessed that the last two fields are set by default, so that it is
> possible not to pass them any value.
> Maybe it is a wrong guess, but i do not know what value can be
> passed for  Maps.Character_Mapping
> 
> Here is a selection from my test procedure 'dimer.adb', where the
> string output_file has been assigned by another procedure:
> 
>     with ada.strings.unbounded;
>     use ada.strings.unbounded;
>     with ada.strings.fixed; use ada.strings.fixed;
>      ...
>      output_file :  unbounded_string ;
>      part1_output_file :  string (1..25) ;
>      ...
>      output_file :=  to_string(output_file);
>      Index(part1_output_file,"put");
>      ...

Index is a function, which must be assigned to a value, so this can't
be the real source. Please include your _complete_ test program, so we
can compile it ourselves, to help get a good answer. 

The default for Map should be fine. You can find out what else you
might pass for Map in the package Ada.Strings.Maps.

-- Stephe




^ permalink raw reply	[relevance 4%]

* Re: DOS/Win95 file names
  @ 1999-06-11  0:00  4%     ` dennison
  1999-06-11  0:00  0%       ` fluffy_pop
  1999-06-11  0:00  4%       ` Robert Dewar
  0 siblings, 2 replies; 132+ results
From: dennison @ 1999-06-11  0:00 UTC (permalink / raw)


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

In article <3762f569.682876310@news.dsuper.net>,
  fluffy_pop@dsuper.net wrote:
> On Fri, 11 Jun 1999 09:03:41 +0200, in comp.lang.ada you wrote:
>
> >...
> >Windows... A possibility is to have an explicit
> >translation table;
>
> I guess this is what you mean:
>      DOS			Windows
> --------------	---------------
> Alt+130 => '�'	Alt+0130 => '�'
> Alt+233 => '_'	Alt+0233 => '�'
>
> FUNCTION ISO ( p_car : character ) RETURN character IS
> WITH Ada.Characters.Latin_1; USE Ada.Characters.Latin_1;
> 	ISO_Char : character;
> BEGIN
> 	CASE character'pos(p_car) IS

Rather than writing this function manually, you should probably look
into using a character mapping from Ada.Strings.Maps.

--
T.E.D.


Sent via Deja.com http://www.deja.com/
Share what you know. Learn what you don't.




^ permalink raw reply	[relevance 4%]

* Re: DOS/Win95 file names
  1999-06-11  0:00  4%     ` dennison
  1999-06-11  0:00  0%       ` fluffy_pop
@ 1999-06-11  0:00  4%       ` Robert Dewar
  1 sibling, 0 replies; 132+ results
From: Robert Dewar @ 1999-06-11  0:00 UTC (permalink / raw)


In article <7jraid$isb$1@nnrp1.deja.com>,
  dennison@telepath.com wrote:
> In article <3762f569.682876310@news.dsuper.net>,
> Rather than writing this function manually, you should
> probably look
> into using a character mapping from Ada.Strings.Maps.


I suspect this is wrong, Ada.Strings.Maps has mapping functions
for Latin-1, but you cannot assume your PC is configured to
use Latin-1. I suggest looking at the csets unit in the
Ada sources to learn about various character set mappings
that are likely to be relevant, including the two most commonly
used PC code pages.


Sent via Deja.com http://www.deja.com/
Share what you know. Learn what you don't.




^ permalink raw reply	[relevance 4%]

* Re: DOS/Win95 file names
  1999-06-11  0:00  4%     ` dennison
@ 1999-06-11  0:00  0%       ` fluffy_pop
  1999-06-11  0:00  4%       ` Robert Dewar
  1 sibling, 0 replies; 132+ results
From: fluffy_pop @ 1999-06-11  0:00 UTC (permalink / raw)


On Fri, 11 Jun 1999 15:38:55 GMT, dennison@telepath.com wrote:

>Rather than writing this function manually, you should probably look
>into using a character mapping from Ada.Strings.Maps.

OK, thanks.  My questions are still unanswered though.  I need to know
what exactly is the code entered into a variable string(i), in my
specific case, when I'm the user working with Win95 and the program is
run in a DOS window.  I can't write this function or use Strings.Maps
if I don't know.  I have to know what I'm working with !

Thanks again.


Marc
--
What I really am is "fluffy", no "_dong",
no "_puff", no "_woo", no  nothing, just plain fluffy.






^ permalink raw reply	[relevance 0%]

* Re: Software landmines (loops)
  @ 1998-09-18  0:00  5%             ` Robert I. Eachus
  0 siblings, 0 replies; 132+ results
From: Robert I. Eachus @ 1998-09-18  0:00 UTC (permalink / raw)


In article <m3pvcv6cr5.fsf@mheaney.ni.net> Matthew Heaney <matthew_heaney@acm.org> writes:

  > I have a string that was padded on the right with blanks.  What I need
  > to do is strip off the blanks, and return the index of the last
  > non-blank character.

  > Let's analyze this problem first using Dijkstra's predicate transformer,
  > and then using Ada...

    Not to disagree with Matt, because he is trying to give an example
of how to reason about a problem, but there is a better approach:

    Ada.Strings.Fixed.Trim(S,Right)'Last

    Of course, you probably want to use the value returned from Trim
instead of just the index of the last non-blank character.
(Technically, if you want to insure that the value returned for a null
string is zero, you need to do:

 function Last_Non_Blank_Index(S: String) return Natural is
   Temp : constant Natural := Ada.Strings.Fixed.Trim(S,Right)'Last;
 begin
   if Temp = S'First then return 0; else return Temp; end if;
 end Last_Non_Blank_Index;

 but the convention of returning 0 in this case was not part of the
original problem statement: 

  > I have a string that was padded on the right with blanks.  What I
  > need to do is strip off the blanks, and return the index of the
  > last non-blank character.

    Why bring this up?  Because when doing ANY kind of engineering,
the first approach to try should be to ask, "Is there something in the
standard catalog that is available off-the-shelf?"  It is so easy and
enjoyable to solve these problems in Ada, that we often lose sight of
how much grief using the library function will save later.  For
example:

    If you need to truncate from both ends?  Change "Right" to "Both".

    If you need to truncate spaces and horizontal tabs from both ends,
and commas and periods from the right:

    with Ada.Strings.Maps, Ada.Characters.Latin_1;
    use Ada.Strings.Maps, Ada.Characters.Latin_1;
    ...
       Ada.Strings.Fixed.Trim(S, To_Set(Space & HT),
             To_Set(Space & HT & Comma & Full_Stop); 

    -- Although I would probably declare the Character_Sets as
    -- constants in some package.

--

					Robert I. Eachus

with Standard_Disclaimer;
use  Standard_Disclaimer;
function Message (Text: in Clever_Ideas) return Better_Ideas is...




^ permalink raw reply	[relevance 5%]

* Re: cookies
  @ 1998-09-17  0:00  3% ` Pascal Obry
  0 siblings, 0 replies; 132+ results
From: Pascal Obry @ 1998-09-17  0:00 UTC (permalink / raw)


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


Lisa Winkworth a �crit dans le message <6tpv6c$o1l$1@emu.cs.rmit.edu.au>...
>Hi, does anyone have any idea how to accept/generally do stuff with cookies
>in ada95??
>Any help would be much appreciated :)
>Thanks in advance,
>Lisa
>


Lisa,

I have done a child package of cgi.ads (from David A. Wheeler) to handle
cookies.

The packages spec/body are small so I have included them in this message.

Pascal.

---------------------------------- CUT
HERE -----------------------------------------------

--         File Name : cgi-cookies.ads
--
--       Created by  : Pascal Obry
--               on  : Mon Mar 10 16:05:01 1997

with Ada.Strings.Unbounded;

package CGI.Cookies is

   use Ada.Strings.Unbounded;

   --  Get cookie number
   function Count return Natural;


   --  Get cookies value
   function Value
     (Key      : in Unbounded_String;
      Required : in Boolean          := False)
      return Unbounded_String;

   function Value
     (Key      : in String;
      Required : in Boolean := False)
      return Unbounded_String;

   function Value
     (Key      : in String;
      Required : in Boolean := False)
      return String;

   function Value
     (Key      : in Unbounded_String;
      Required : in Boolean          := False)
      return String;


   --  Was a given key provided?
   function Key_Exists (Key : in String)           return Boolean;
   function Key_Exists (Key : in Unbounded_String) return Boolean;


   --  Set cookies value
   procedure Set (Key     : in String;
                  Value   : in String;
                  Expires : in String  := "";
                  Path    : in String  := "/";
                  Domain  : in String  := "";
                  Secure  : in Boolean := False);


   --  Send cookies to client with HTML header.
   procedure Put_CGI_Header_With_Cookies
     (Header : in String := "Content-type: text/html");

end CGI.Cookies;


--         File Name : cgi-cookies.adb
--
--       Created by  : Pascal Obry
--               on  : Mon Mar 10 16:05:01 1997

with Ada.Text_IO;
with Ada.Strings.Maps;
with Ada.Characters.Handling;

with Table_Of_Static_Keys_And_Static_Values_G;

package body CGI.Cookies is

   use Ada;
   use Ada.Strings.Maps;

   --  to set cookie
   type Key_Values_Record is
      record
         Value   : Unbounded_String;
         Expires : Unbounded_String;
         Path    : Unbounded_String;
         Domain  : Unbounded_String;
         Secure  : Boolean := False;
      end record;

   package Cookie_Table is
      new Table_Of_Static_Keys_And_Static_Values_G (Unbounded_String,
                                                    "<",
                                                    "=",
                                                    Key_Values_Record);

   --  to hold cookie value sent be the client
   type Key_Value_Pair is
      record
         Key   : Unbounded_String;
         Value : Unbounded_String;
      end record;

   type Key_Value_Sequence is array (Positive range <>) of Key_Value_Pair;
   type Access_Key_Value_Sequence is access Key_Value_Sequence;

   -- The following are data internal to this package.

   Cookie_Data     : Access_Key_Value_Sequence;

   Set_Cookie_Data : Cookie_Table.Table_Type;


   Ampersands :    constant Character_Set      := To_Set ('&');
   Equals     :    constant Character_Set      := To_Set ('=');
   Plus_To_Space : constant Character_Mapping  := To_Mapping ("+", " ");


                      ------------------------------

   --  Get cookie number
   function Count return Natural is
   begin
      if Cookie_Data = null then
         return 0;
      else
         return Cookie_Data'Length;
      end if;
   end Count;
                      ------------------------------


   --  Get cookies value
   function Value
     (Key      : in Unbounded_String;
      Required : in Boolean          := False)
      return Unbounded_String is
   begin
      for I in 1 .. Count loop
         if Cookie_Data (I).Key = Key then
            return Cookie_Data (I).Value;
         end if;
      end loop;

      -- Didn't find the Key.
      if Required then
         raise Constraint_Error;
      else
         return Null_Unbounded_String;
      end if;
   end Value;

                      ------------------------------

   function Value
     (Key      : in String;
      Required : in Boolean := False)
      return Unbounded_String
   is
   begin
      return Value (To_Unbounded_String (Key), Required);
   end Value;

                      ------------------------------

   function Value
     (Key      : in String;
      Required : in Boolean := False)
      return String
   is
   begin
      return To_String (Value (To_Unbounded_String (Key), Required));
   end Value;

                      ------------------------------

   function Value
     (Key      : in Unbounded_String;
      Required : in Boolean          := False)
      return String
   is
   begin
      return To_String (Value (Key, Required));
   end Value;


                      ------------------------------

   --  Was a given key provided?
   function Key_Exists (Key : in Unbounded_String)
                        return Boolean
   is
   begin
      for I in 1 .. Count loop
         if Cookie_Data (I).Key = Key then
            return True;
         end if;
      end loop;
      return False;
   end Key_Exists;

                      ------------------------------

   function Key_Exists (Key : in String)
                        return Boolean
   is
   begin
     return Key_Exists (To_Unbounded_String (Key));
   end Key_Exists;


                      ------------------------------

   --  Set cookie value
   procedure Set (Key     : in String;
                  Value   : in String;
                  Expires : in String := "";
                  Path    : in String := "/";
                  Domain  : in String := "";
                  Secure  : in Boolean := False)
   is
      Cookie_Record : Key_Values_Record;
   begin -- Set_Cookies
      Cookie_Record := (To_Unbounded_String (Value),
                        To_Unbounded_String (Expires),
                        To_Unbounded_String (Path),
                        To_Unbounded_String (Domain),
                        Secure);

      Cookie_Table.Insert_Or_Replace_Value (Set_Cookie_Data,
                                            To_Unbounded_String (Key),
                                            Cookie_Record);
   end Set;


                      ------------------------------

   procedure Put_CGI_Header_With_Cookies
     (Header : in String := "Content-type: text/html")
   is

      procedure Put_Cookie (Key      : in     Unbounded_String;
                            Datas    : in     Key_Values_Record;
                            N        : in     Positive;
                            Continue : in out Boolean) is
      begin
         Text_IO.Put ("Set-Cookie: ");
         Text_IO.Put (To_String (Key) & '=' & To_String (Datas.Value));

         if Datas.Expires /= Null_Unbounded_String then
            Text_IO.Put ("; expires=" & To_String (Datas.Expires));
         end if;

         if Datas.Path /= Null_Unbounded_String then
            Text_IO.Put ("; path=" & To_String (Datas.Path));
         end if;

         if Datas.Domain /= Null_Unbounded_String then
            Text_IO.Put ("; domain=" & To_String (Datas.Domain));
         end if;

         if Datas.Secure then
            Text_IO.Put ("; secure");
         end if;

         Text_IO.New_Line;

         Continue := True;
      end Put_Cookie;


      procedure For_Every_Cookies is
         new Cookie_Table.Traverse_ASC_G (Put_Cookie);

   begin
      --  CGI Header
      Text_IO.Put_Line (Header);

      --  Cookies
      For_Every_Cookies (Set_Cookie_Data);
      Text_IO.New_Line;
   end Put_CGI_Header_With_Cookies;





                      ------------------------------

   -- Initialization routines, including some private procedures only
   -- used during initialization.

   function Field_End
     (Data            : Unbounded_String;
      Field_Separator : Character;
      Starting_At     : Positive         := 1)
      return Natural
   is
      -- Return the end-of-field position in Data after "Starting_Index",
      -- assuming that fields are separated by the Field_Separator.
      -- If there's no Field_Separator, return the end of the Data.
   begin
      for I in Starting_At .. Length (Data) loop
         if Element (Data, I) = Field_Separator then
            return I - 1;
         end if;
      end loop;
      return Length (Data);
   end Field_End;

                      ------------------------------

   function Hex_Value (H : in String) return Natural is
      -- Given hex string, return its Value as a Natural.
      Value : Natural := 0;
   begin
      for P in 1.. H'Length loop
         Value := Value * 16;

         if H(P) in '0' .. '9' then
            Value := Value + Character'Pos(H(P)) - Character'Pos('0');
         elsif H(P) in 'A' .. 'F' then
            Value := Value + Character'Pos(H(P)) - Character'Pos('A') + 10;
         elsif H(P) in 'a' .. 'f' then
            Value := Value + Character'Pos(H(P)) - Character'Pos('a') + 10;
         else
            raise Constraint_Error;
         end if;

      end loop;
      return Value;
   end Hex_Value;

                      ------------------------------

   procedure Decode (Data : in out Unbounded_String)
   is
      use Characters.Handling;
      I : Positive := 1;
      -- In the given string, convert pattern %HH into alphanumeric
characters,
      -- where HH is a hex number. Since this encoding only permits values
      -- from %00 to %FF, there's no need to handle 16-bit characters.
   begin
      while I <= Length(Data) - 2 loop
         if Element (Data, I) = '%' and
           Is_Hexadecimal_Digit (Element (Data, I+1)) and
           Is_Hexadecimal_Digit (Element (Data, I+2)) then

            Replace_Element
              (Data, I,
               Character'Val (Hex_Value (Slice (Data, I+1, I+2))));
            Delete (Data, I+1, I+2);
         end if;
         I := I + 1;
      end loop;
   end Decode;
                      ------------------------------

   procedure Set_CGI_Position
     (Key_Number : in Positive;
      Datum      : in Unbounded_String)
   is
      Last : Natural := Field_End(Datum, '=');
      -- Given a Key number and a datum of the form key=value
      -- assign the CGI_Data(Key_Number) the values of key and value.
   begin
      Cookie_Data (Key_Number).Key
        := To_Unbounded_String (Slice (Datum, 1, Last));
      Cookie_Data (Key_Number).Value
        := To_Unbounded_String (Slice (Datum, Last+2, Length (Datum)));
      Decode (Cookie_Data (Key_Number).Key);
      Decode (Cookie_Data (Key_Number).Value);
   end Set_CGI_Position;

                      ------------------------------

   procedure Set_CGI_Data (Raw_Data : in Unbounded_String) is
      -- Set CGI_Data using Raw_Data.
      Key_Number         : Positive := 1;
      Character_Position : Positive := 1;
      Last : Natural;
   begin
      while Character_Position <= Length (Raw_Data) loop
         Last := Field_End (Raw_Data, ';', Character_Position);
         Set_CGI_Position
           (Key_Number,
            To_Unbounded_String (Slice (Raw_Data, Character_Position,
Last)));
         Character_Position := Last + 3; -- Skip over field separator. "; "
         Key_Number := Key_Number + 1;
      end loop;
   end Set_CGI_Data;

                      ------------------------------

   procedure Initialize is
      Raw_Data : Unbounded_String;
   begin
      Raw_Data := To_Unbounded_String (Get_Environment("HTTP_COOKIE"));

      Translate (Raw_Data, Mapping => Plus_To_Space);

      if Length (Raw_Data) > 0 then
         Cookie_Data :=
           new Key_Value_Sequence (1 .. Count (Raw_Data, ";") + 1);
         Set_CGI_Data (Raw_Data);
      end if;

   end Initialize;

begin
   Initialize;
end CGI.Cookies;
---------------------------------- CUT
HERE -----------------------------------------------






^ permalink raw reply	[relevance 3%]

* Re: Parsing a line into strings
    @ 1998-07-11  0:00  6% ` david.c.hoos.sr
  1 sibling, 0 replies; 132+ results
From: david.c.hoos.sr @ 1998-07-11  0:00 UTC (permalink / raw)


In article <35A3A199.D55C3153@oit.edu>,
  C N <netzelc@oit.edu> wrote:
> Hi all,
>
>     I've been looking for a comand in Ada that is equivilent to C's
> "strtok" .  So far - no luck.
> I need to break up a line that is read in from a file with the strings
> delimited by comas and spaces.
>
>     If this command does'nt exhist, would anyone be willing to share a
> chunk of code they've developed that performs this operation?
>
>     Any and all responses are greatly appreaciated,
>
> -=Chris=-
>
> -=// "Even a blind squrrel finds a nut once in a while." \\=-
>

The program at the end of this message will parse the string submitted
as the first command line argument into tokens delimited by any of the
characters in the string submitted as the second command line
argument, and print the tokens one at a time to the standard output.

--- begin program source code ----
with Ada.Command_Line;
with Ada.Strings.Fixed;
with Ada.Strings.Maps;
with Ada.Text_Io;
procedure Tokenize is
begin
   if Ada.Command_Line.Argument_Count /= 2 then
      Ada.Text_Io.Put_Line (Ada.Text_Io.Standard_Error,
         "USAGE:" &
         Ada.Command_Line.Command_Name &
         " <string to be tokenized> <delimiters>");
      Ada.Command_Line.Set_Exit_Status (Ada.Command_Line.Failure);
      return;
   end if;
   declare
      The_String : constant String := Ada.Command_Line.Argument (1);
      The_Delimiters : constant Ada.Strings.Maps.Character_Set :=
      Ada.Strings.Maps.To_Set (Ada.Command_Line.Argument(2));
      First : Positive;     -- Index of first character in token
      Last : Natural := 0;  -- Index of last character in token (also used
      -- incremented by 1 -- as the starting point for next search).
   begin
      loop
         Ada.Strings.Fixed.Find_Token
         (Source => The_String (Last + 1 .. The_String'Last),
            Set => The_Delimiters,
            Test => Ada.Strings.Outside,
            First => First,
            Last => Last);
         exit when Last = 0;
         Ada.Text_Io.Put_Line
         ("Token => """ & The_String (First .. Last) & """");
      end loop;
   end;
end Tokenize;
--- end program source code ----


-----== Posted via Deja News, The Leader in Internet Discussion ==-----
http://www.dejanews.com/rg_mkgrp.xp   Create Your Own Free Member Forum




^ permalink raw reply	[relevance 6%]

* Re: Parsing a line into strings
  @ 1998-07-09  0:00  5%           ` Brian Rogoff
  0 siblings, 0 replies; 132+ results
From: Brian Rogoff @ 1998-07-09  0:00 UTC (permalink / raw)


On 8 Jul 1998, Robert Dewar wrote:
> 
> In fact GNAT.Spitbol uses Unrestricted_Access in a pretty fundamental
> way, having nothing at all to do with downward funargs!

That sound you hear is me removing my foot from my mouth :-)

In order to do penance, I have to post Ada code. Since the original poster 
was asking for the functionality of strtok in Ada, let me take a stab at
it; note that I won't diddle the state of the string like strtok does, but 
this is pretty much it. Since the caller knows the start position its easy
to use slices to extract the "tokens". Hacked and not tested, as usual :-)

-- Brian

with Ada.Strings.Maps;
use Ada.Strings.Maps;

procedure String_Separator_Position (Input : in String ; 
                                     Separators : in Character_Set;
                                     Start : in out Integer) is 
    Pos : Integer := Start;
begin
    if Start < Input'First or Start > Input'Last then 
        return; -- or raise an exception, or whatever...
    end if;

    for I in Start .. Input'Last loop
        if Is_In(Input(I),Separators) then 
            Start := I;
            return;
        end if;
    end loop;
end String_Separator_Position;


    





^ permalink raw reply	[relevance 5%]

* Re: String Manipulation - Help Needed
  @ 1998-04-05  0:00  5% ` Matthew Heaney
  0 siblings, 0 replies; 132+ results
From: Matthew Heaney @ 1998-04-05  0:00 UTC (permalink / raw)



In article <x3g0MCAC5AK1EwY0@roslyn.demon.co.uk>, Howard Davies
<Howard@roslyn.demon.co.uk> wrote:

>Hi,
>I have a sentence stored in a string and I need to remove all spaces and
>punctuation from the string.
>My 600 page Ada book just says that this requies advanced packages that
>are beyond the scope of the book.
>Can someone help me out?

There are packages that come with the language to do what you want.  The
packages are

Ada.Strings.Fixed
Ada.Strings.Bounded
Ada.Strings.Unbounded
Ada.Strings.Maps
Ada.Characters.Handling

The Trim subprograms can remove whitespace from a string.  Maybe you can
make use of the character mapping functions too.




^ permalink raw reply	[relevance 5%]

* Re: general-purpose vs. domain-specific programming languages
@ 1998-01-05  0:00  4% Marin David Condic, 561.796.8997, M/S 731-96
  0 siblings, 0 replies; 132+ results
From: Marin David Condic, 561.796.8997, M/S 731-96 @ 1998-01-05  0:00 UTC (permalink / raw)



"Terry J. Westley" <westley@CALSPAN.COM> writes:
>Here are the sorts of questions I would like such research to address:
>   Why do people use Perl so much for CGI programming?
>   Why can't I write some libraries so that Ada is just as easy to
>      use to search and replace data in text files as Perl?
>   Why is string and list handling so much easier in Tcl and Perl
>      than in Ada?
>
    I don't know Perl, so I can't speak to specific features. It would
    seem that even in a 'string friendly' language like Perl, you'd
    still need to specify certain things like the source file, the
    object file, the string (or meta-string?) to search for and the
    string with which to replace it. In Ada, you might build a package
    like this:

    package Perl_Like_Utilities is

        procedure Search_And_Replace (
            Source_File     : in     String ;   --  OS dependent filename.
            Object_File     : in     String ;   --  OS dependent filename.
            Search          : in     String ;
            Replace         : in     String) ;

        --  And whatever else you think you need.

    end Perl_Like_Utilities ;

    Then using Text_IO or Stream_IO and the various string
    manipulation packages, you could build up the procedures you need.
    Of course, at this point, you are acting in the same capacity as
    the Perl-primitive-implementor. The guy who had to code up the
    behavior of the Search_And_Replace primitive (whatever it is in
    Perl) had to operate by reading the file and laboriously comparing
    characters - probably in assembler. But its a job you only do
    once.

    I'll agree that the string handling packages in Ada (See "Strings
    - A.4.1" in the ARM for the description of Ada.Strings,
    Ada.Strings.Maps, Ada.Strings.Fixed, Ada.Strings.Bounded,
    Ada.Strings.Unbounded) can be confusing. They don't provide the
    utilities that *I* would have written (everybody has their own
    favorite way of doing things) but they are fairly "regular"
    ("orthogonal" is also a favorite term) and they will usually get
    the job done. As with anything else, you've got to spend the time
    to learn "The Ada Way" of doing it and not try to write Perl (or
    Snobol, or Lisp, or Basic) only with Ada syntax.

    I'd suspect that if you could come up with a list of your favorite
    Perl primitives and a description of their semantics, it would be
    possible to build an Ada package that provided equivalent
    features, perhaps by utilizing the Ada.Strings... packages as the
    underlying implementation. (Maybe you'd like to e-mail me some
    examples and we could investigate how difficult the job might be.)
    A decent specification might even gain some wider acceptance as a
    defacto standard if it was circulated widely.

    MDC

Marin David Condic, Senior Computer Engineer     Voice:     561.796.8997
Pratt & Whitney GESP, M/S 731-96, P.O.B. 109600  Fax:       561.796.4669
West Palm Beach, FL, 33410-9600                  Internet:  CONDICMA@PWFL.COM
=============================================================================
    "Outside of a dog, a book is man's best friend; inside a dog,
    it's too dark to read..."
        --  Groucho Marx
=============================================================================




^ permalink raw reply	[relevance 4%]

* Re: comand line arguments
@ 1997-10-13  0:00  5% Marin David Condic, 561.796.8997, M/S 731-96
  0 siblings, 0 replies; 132+ results
From: Marin David Condic, 561.796.8997, M/S 731-96 @ 1997-10-13  0:00 UTC (permalink / raw)



    Here's some code that should at least get you started developing
    whatever you need for processing a command line.

    MDC

Marin David Condic, Senior Computer Engineer     Voice:     561.796.8997
Pratt & Whitney GESP, M/S 731-96, P.O.B. 109600  Fax:       561.796.4669
West Palm Beach, FL, 33410-9600                  Internet:  CONDICMA@PWFL.COM
===============================================================================
    "Eagles may soar, but a weasle never gets sucked up into a jet engine."
===============================================================================

--
--  This function will return a string containing everything that
--  was on the command line. Due to OS pecularities, you may not
--  get it back exactly as typed. You may not get everything you
--  want, either. Ada can't fix that because it's going to depend on
--  what the OS decides to give you. From experience, Unix and WinNT
--  will produce different effects from the same code.
--
--  A lot of this implementation depends on what sort of command line
--  "language" you intend to be parsing out of the string. You'll
--  have to tailor the function as needed, but it at least
--  illustrates the proper calls to Ada.Command_Line.
--
--  The function presumes that you don't care about spaces between
--  parameters. You could modify it to put spaces between the
--  parameters, etc.
--

with Ada.Command_Line ;
with Ada.Strings ;
with Ada.Strings.Maps ;
with Ada.Strings.Fixed ;
with Ada.Characters.Handling ;
with Ada.Text_IO ;

function Get_Command_Line return String is
    --
    Temp            : String (1..256)   := (others => ' ') ;
    I               : Natural           := 0 ;
    --
    use Ada.Command_Line ;
    use Ada.Strings.Fixed ;
begin
    --
    --  Get the "command" or program name from the system if available.
    --
    Ada.Strings.Fixed.Move (
        Source  => Ada.Command_Line.Command_Name,
        Target  => Temp,
        Drop    => Ada.Strings.Right) ;
    --
    --  Get each of the args into the string - spaces don't matter.
    --
    I := Ada.Strings.Fixed.Index (
        Source  => Temp,
        Pattern => " ") ;
    for X in 1..Ada.Command_Line.Argument_Count loop
        Ada.Strings.Fixed.Move (
            Source  => Ada.Command_Line.Argument (X),
            Target  => Temp (I..Temp'Last),
            Drop    => Ada.Strings.Right) ;
        I := Index_Non_Blank (
            Source  => Temp,
            Going   => Ada.Strings.Backward) + 1 ;
    end loop ;
    --
    return Ada.Strings.Fixed.Trim (
        Source  => Temp,
        Side    => Ada.Strings.Both) ;
exception
    when Constraint_Error =>
        Ada.Text_IO.Put_Line ("Your command line is probably too long.") ;
        return "" ;
end Get_Command_Line ;




^ permalink raw reply	[relevance 5%]

* Re: How do I allocate strings of variable length at runtime?
  @ 1997-09-29  0:00  5%   ` Marc Bejerano
  0 siblings, 0 replies; 132+ results
From: Marc Bejerano @ 1997-09-29  0:00 UTC (permalink / raw)



Just use Ada.Strings.Unbounded and when you need to call Text_IO.Open simply
pass it the To_String version of your variable. For example:

with Ada.Strings.Unbounded; use Ada.Strings.Unbounded;
with Ada.Text_IO; use Ada.Text_IO;

...
fileName: Unbounded_String;
inputFile: File_Type;

fileName := To_Unbounded_String ("whatever.data");
Open (inputFile, In_File, To_String (fileName);

This will solve your dilemma regarding the blanks at he end of the string.
Alternatively, you could use the Ada.Strings.Maps package and physically
Trim(...) the string prior to passing it to the Open call.

-Marc

P.S. Remember, keep it simple.

Matthew Heaney wrote:

> In article <342bbda6.153101@news.rmi.de>, hilgend@rmi.de (Oliver
> Hilgendorf) wrote:
>
> >I want to open several textfiles using text_io.open. The length of
> >each filename is only know at runtime. However if I define a string of
> >the maximum filename-length to hold the filename, all trailing blanks
> >are also passed to text_io.open and this results in name_error because
> >a file with trailing blanks does not exist.
> >So I have to pass a string that is defined with exactly the same
> >length as the actual filename.
> >How can I define a string object with variable length at runtime?
>
> You need to specify more information: What is the source of filenames?  Do
> you have to store the filenames prior to opening the files?
>

<snip>






^ permalink raw reply	[relevance 5%]

* Re: Standard library and distributed systems
  1997-07-03  0:00  5%   ` Andre Spiegel
@ 1997-07-07  0:00  4%     ` Tucker Taft
  0 siblings, 0 replies; 132+ results
From: Tucker Taft @ 1997-07-07  0:00 UTC (permalink / raw)



Andre Spiegel (spiegel@inf.fu-berlin.de) wrote:

: Thanks, Tucker, for your detailed reply.  You wrote:

: > Rather than removing things from these packages (which could be very
: > disruptive to existing Ada 95 code), we could envision
: > additional pragmas or rules to make them "safe."    The simplest
: > would be to have a pragma Not_Remote_Type(type); which could
: > simply mark a given type that happens to be declared in a 
: > Remote_Types package as not being allowed as a formal parameter type
: > in a remotely callable subprogram.

: The operations declared in a Remote_Types package are not "remotely
: callable subprograms", are they?  (Each partition that withes such a
: package gets its own copy; the only thing that's passed across
: partition boundaries are values of _types_ declared in such a
: package.)

: That means, for example, that Ada.Strings.Bounded doesn't make any
: "problematic" use of Ada.Strings.Maps.Character_Mapping_Function (it's
: only used as a parameter for some of the subprograms).  It would only
: be "problematic" if a Character_Mapping_Function were part of a _type_
: declared in Ada.Strings.Bounded.

: So how about this rule: a Remote_Types package may "with" a package
: that is not pure (and not Remote_Types), _provided_ that it doesn't
: make "problematic" use of it.

That would make some sense, since the body of a Remote_Types package
is completely unrestricted.  Essentially you would have to ensure
that it doesn't "reexport" evil things in its spec from some evil 
"with"ed unit.

: Maybe such a rule could enhance distributability of general Ada
: applications?  The additional rule would be even less expensive (or,
: intrusive) than an additional pragma.  (But of course it couldn't solve
: the problem of String_Access, so we'd need the pragma also.)

In general the Distributed Systems Annex was breaking new ground,
and I at least saw it as an initial cut at providing distribution
in the language.  Using the Ada/Corba bindings is another good way.
Defining a different set of pragmas is yet a third way.

Of course, the goal is to have something that is supported by
a critical mass of Ada 95 compilers, independent of whether it
is in the "official" ISO reference manual.  If you consider Annex E
as a "proof of concept" rather than as a finished product, then
identifying a small set of additional rules and pragmas to augment its
functionality seems completely appropriate, IMHO.  Getting them 
implemented by that "critical mass" is the next challenge...

--
-Tucker Taft   stt@inmet.com   http://www.inmet.com/~stt/
Intermetrics, Inc.  Burlington, MA  USA




^ permalink raw reply	[relevance 4%]

* Re: Standard library and distributed systems
  1997-07-02  0:00  4% ` Tucker Taft
@ 1997-07-03  0:00  5%   ` Andre Spiegel
  1997-07-07  0:00  4%     ` Tucker Taft
  0 siblings, 1 reply; 132+ results
From: Andre Spiegel @ 1997-07-03  0:00 UTC (permalink / raw)



Thanks, Tucker, for your detailed reply.  You wrote:

> Rather than removing things from these packages (which could be very
> disruptive to existing Ada 95 code), we could envision
> additional pragmas or rules to make them "safe."    The simplest
> would be to have a pragma Not_Remote_Type(type); which could
> simply mark a given type that happens to be declared in a 
> Remote_Types package as not being allowed as a formal parameter type
> in a remotely callable subprogram.

The operations declared in a Remote_Types package are not "remotely
callable subprograms", are they?  (Each partition that withes such a
package gets its own copy; the only thing that's passed across
partition boundaries are values of _types_ declared in such a
package.)

That means, for example, that Ada.Strings.Bounded doesn't make any
"problematic" use of Ada.Strings.Maps.Character_Mapping_Function (it's
only used as a parameter for some of the subprograms).  It would only
be "problematic" if a Character_Mapping_Function were part of a _type_
declared in Ada.Strings.Bounded.

So how about this rule: a Remote_Types package may "with" a package
that is not pure (and not Remote_Types), _provided_ that it doesn't
make "problematic" use of it.

Maybe such a rule could enhance distributability of general Ada
applications?  The additional rule would be even less expensive (or,
intrusive) than an additional pragma.  (But of course it couldn't solve
the problem of String_Access, so we'd need the pragma also.)




^ permalink raw reply	[relevance 5%]

* Standard library and distributed systems
@ 1997-07-02  0:00  6% Andre Spiegel
  1997-07-02  0:00  4% ` Tucker Taft
  0 siblings, 1 reply; 132+ results
From: Andre Spiegel @ 1997-07-02  0:00 UTC (permalink / raw)



Last week I posted an article concerning distributability of types in
Ada's standard library.  There were no replies, so here is a second
try, hopefully a bit clearer.

The problem: Ada.Strings.Bounded and Ada.Strings.Unbounded are not
Remote_Types packages, which means that you cannot use bounded or
unbounded strings for interpartition communications in a distributed
system.  Since these types are very important, I find this a severe
restriction for distributed programming in Ada, and I wonder whether
this could be changed.

There is a proposal, documented in Ada Issue ai-00126 to make all
standard packages Remote_Types for which it is possible.  But even
under this proposal, Ada.Strings.Bounded and Ada.Strings.Unbounded
remain non-remote.

  (1) Ada.Strings.Bounded cannot be Remote_Types because it depends
      on Ada.Strings.Maps, which, according to ai-00126, cannot be 
      Remote_Types because it declares an access-to-subprogram type, 
      Character_Mapping_Function.

      I don't understand this.  According to RM95 E.2.2(9), a 
      Remote_Types package _may_ declare access-to-subprogram types.
      So I think that both Ada.Strings.Maps and Ada.Strings.Bounded
      could be Remote_Types.

  (2) Ada.Strings.Unbounded cannot be Remote_Types for an additional 
      reason: it declares type String_Access.  

      But this type is not used anywhere else in the visible part, and 
      I recall that people have been discussing whether this declaration 
      should be removed.  If it were removed, and Ada.Strings.Unbounded 
      privately defined Read and Write attributes for Unbounded_String, 
      then the type could be used for interpartition communications.

  (3) If, for example, Ada.Strings.Bounded were Remote_Types, I cannot
      imagine a scenario where Ada.Strings.Maps.Character_Mapping_Function
      would actually be used remotely (so that the function being pointed
      to would actually be called across partitions).  If this is correct,
      could it be that the language rules are too restrictive in this area?
      They forbid something which actually wouldn't cause any problems?

Please let me know whether the above reasoning is correct.  If not,
please tell me why not.  If it _is_ correct, is it planned to change
the standard library and/or the language rules?

Thanks,

Andre Spiegel
Free University of Berlin




^ permalink raw reply	[relevance 6%]

* Re: Standard library and distributed systems
  1997-07-02  0:00  6% Standard library and distributed systems Andre Spiegel
@ 1997-07-02  0:00  4% ` Tucker Taft
  1997-07-03  0:00  5%   ` Andre Spiegel
  0 siblings, 1 reply; 132+ results
From: Tucker Taft @ 1997-07-02  0:00 UTC (permalink / raw)



Andre Spiegel (spiegel@inf.fu-berlin.de) wrote:

: Last week I posted an article concerning distributability of types in
: Ada's standard library.  There were no replies, so here is a second
: try, hopefully a bit clearer.

: The problem: Ada.Strings.Bounded and Ada.Strings.Unbounded are not
: Remote_Types packages, which means that you cannot use bounded or
: unbounded strings for interpartition communications in a distributed
: system.  Since these types are very important, I find this a severe
: restriction for distributed programming in Ada, and I wonder whether
: this could be changed.
: ... 

I basically agree that we should endeavor to make all "interesting"
standard packages compatible either with pragma Pure or Remote_Types.
For Remote_Types, the package spec has to be preelaborable, and
any access types declared in the visible part of the package spec
are considered "remote" access types.  There are a number of restrictions
on the declaration and use of remote access types, and the 
Character_Mapping_Function in Ada.Strings.Maps and the String_Access
in Ada.Strings.Unbounded just don't cut it.

Rather than removing things from these packages (which could be very
disruptive to existing Ada 95 code), we could envision
additional pragmas or rules to make them "safe."    The simplest
would be to have a pragma Not_Remote_Type(type); which could
simply mark a given type that happens to be declared in a 
Remote_Types package as not being allowed as a formal parameter type
in a remotely callable subprogram.  For String_Access, an alternative
is to allow such a visible access type declaration to exist so long 
as there are 'Write and 'Read attributes specified that can safely 
transport such a value between partitions.  

For String_Access, it seems pretty obvious what 'Write/'Read would do,
namely have 'Write convert the access value into a stream representation 
of the designated string, and then have 'Read re-allocate the string in 
the heap on the receiving end.  Of course, this could end up as a 
horrible storage leak, so better might be to simply disallow String_Access
as a parameter type in remote calls.

In any case, I agree it would be nice to push Remote_Types further.
However, in the interim, using type String (or your own type) as the 
parameter type for a remote call, and doing the conversion to/from 
Unbounded_String manually does not seem excessively painful, since that 
is essentially what the 'Write/'Read for Unbounded_String must be doing 
anyway.

: Andre Spiegel
: Free University of Berlin

-Tucker Taft   stt@inmet.com   http://www.inmet.com/~stt/
Intermetrics, Inc.  Burlington, MA  USA




^ permalink raw reply	[relevance 4%]

* Re: What's Pure for Dist Sytems?
  @ 1997-06-24  0:00  6%     ` Andre Spiegel
  0 siblings, 0 replies; 132+ results
From: Andre Spiegel @ 1997-06-24  0:00 UTC (permalink / raw)



Robert Dewar writes:

> Andre says
> 
> <<However, even under this proposal, Ada.Strings.Bounded and
> Ada.Strings.Unbounded are still non-remote.  I find this an
> intolerable restriction, too, and I wonder if anyone sets out to
> remedy this...>>

> Finding something intolerable does not constitute a solution. I assume you
> understand *why* this rule is there. What is your proposal to "remedy this".

As a matter of fact, I don't fully understand why these packages
cannot be Remote_Types.  This is how far I can follow the reasoning
(please correct me if I'm wrong on any of this)

  - Ada.Strings.Unbounded cannot be remote, because

    (a) it depends on Ada.Strings.Maps, which cannot be pure because
        it declares an access-to-subprogram type
        (Character_Mapping_Function).  But I don't see why this
        package cannot be Remote_Types.

    (b) Ada.Strings.Unbounded declares type String_Access, which is
        however not needed in the rest of the spec, and I recall that
        some people wondered if this type should be removed from the
        visible part of the specification.

    (c) if these two problems weren't there, one only would have to
        make sure that the package privately defines Read and Write
        attributes for Unbounded_String -- something that the GNAT
        version of the package already seems to do, judging from
        what I saw last time I looked.

   - Ada.Strings.Bounded cannot be remote, because it depends on 
     Ada.Strings.Maps -- same reason as above.  I don't see any other
     obstacles for Ada.Strings.Bounded.

But what is the problem with Character_Mapping_Function anyway?  If
the string packages were Remote_Types, and Ada.Strings.Maps wasn't,
how could a Character_Mapping_Function be used remotely then -- except
by withing Ada.Strings.Maps _directly_ in the spec of a
Remote_Call_Interface?

RM95 E.2.2(6) says that a Remote_Types unit may only depend
semantically on declared pure, remote types, or shared passive units.
As far as I understand, this rule ensures that no remote variable
reference, remote rendezvous, or unwanted remote access to anything is
possible in a program.  However, the predefined string packages use
Ada.Strings.Maps only in such a way that no problems could arise from
this, even if Ada.Strings.Maps had something in it that couldn't be
made remote.

So maybe the package categorization rules forbid more than they would
have to?  Could this be helped by different, possibly more complex
rules that only forbid things that really cause problems?

Andre Spiegel
Free University of Berlin





^ permalink raw reply	[relevance 6%]

* Re: Equality operator overloading in ADA 83
  @ 1997-04-22  0:00  3%     ` Robert A Duff
  0 siblings, 0 replies; 132+ results
From: Robert A Duff @ 1997-04-22  0:00 UTC (permalink / raw)



In article <335CAEFE.35DC@elca-matrix.ch>,
Mats Weber  <Mats.Weber@elca-matrix.ch> wrote:
>The same holds for Ada.Strings.Unbounded, and there was some discussion
>on this a year ago or so here in c.l.a. Is anything being done so that
>an AI is issued to ensure this (if AIs still exist) ?

This is AI95-123, which has been approved by the ARG, but not (yet) by
WG9.  I've included it below.  In general, I believe that ACVC tests do
not get written based on AIs until WG9 has approved.

In case anyone's interested, the AI's are stored on
sw-eng.falls-church.va.us, in /public/adaic/standards/95com/ada-issues.

- Bob

!standard 04.05.02 (24)                               97-03-19  AI95-00123/05
!class binding interpretation 96-07-23
!status ARG approved 10-0-2 (subject to editorial review)  96-10-07
!status work item (letter ballot was 6-6-0) 96-10-03
!status ARG approved 8-0-0 (subject to letter ballot) 96-06-17
!status work item 96-04-04
!status received 96-04-04
!priority High
!difficulty Medium
!subject Equality for Composite Types

!summary 96-11-19

The primitive equality operators of language defined types compose
properly, when the type is used as a component type, or a generic actual
type.

For any composite type, the order in which "=" is called for components
is not defined by the language.  Furthermore, if the result is
determined before calling "=" on some components, the language does not
define whether "=" is called on those components.

!question 96-07-23

The following language-defined types are private, and have an explicitly
defined primitive "=" operator:

    System.Address
    Ada.Strings.Maps.Character_Set
    Ada.Strings.Bounded.Generic_Bounded_Length.Bounded_String
    Ada.Strings.Unbounded.Unbounded_String
    Ada.Strings.Wide_Maps.Wide_Character_Set
    Ada.Task_Identification.Task_ID

This would seem to imply that the composability of these "=" operators
depends on whether the implementation chooses to implement them as
tagged types, by 4.5.2(14-24):

  14   For a type extension, predefined equality is defined in terms of the
  primitive (possibly user-defined) equals operator of the parent type and of
  any tagged components of the extension part, and predefined equality for any
  other components not inherited from the parent type.

  15   For a private type, if its full type is tagged, predefined equality is
  defined in terms of the primitive equals operator of the full type; if the
  full type is untagged, predefined equality for the private type is that of
  its full type.
  ...
  21   Given the above definition of matching components, the result of the
  predefined equals operator for composite types (other than for those
  composite types covered earlier) is defined as follows:

     22  If there are no components, the result is defined to be True;

     23  If there are unmatched components, the result is defined to be
         False;

     24  Otherwise, the result is defined in terms of the primitive equals
         operator for any matching tagged components, and the predefined
         equals for any matching untagged components.

This would cause portability problems.

Also, in the above definition, what does "in terms of" mean?  For a
composite type, if some parts have an "=" with side effects, does the
language define whether all of these side effects happen, and in what
order?

!recommendation 96-11-16

(See summary.)

!wording 96-07-23

!discussion 97-03-19

Composability of equality means three things:

    1. If a composite type has a component of type T with a user-defined
       equality operator, then the predefined equality of the composite
       type calls the user-defined equality operator of type T (for that
       component).

    2. If an actual type T for a generic formal type has a user-defined
       equality operator, then the predefined equality on the generic
       formal type calls the user-defined equality operator of type T.

    3. If a parent type T has a user-defined equality operator, then the
       predefined equality of a type extension of T calls the
       user-defined equality on T (for the parent part), in addition to
       comparing the extension parts.

Non-composability means that the predefined equality is called for T,
despite the fact that T has a user-defined equality operator.  Of
course, if there is no user-defined equality, then equality always
composes properly.

Number 3 is irrelevant here, since none of the types in question is
(visibly) tagged.

For a private type, if the underlying type is tagged, or if there is no
user-defined equality, then equality composes.  Otherwise, it does not.
(Here, "underlying type" means the full type, or if that comes from a
private type, then the underlying type of *that* type, and so on.)

However, for the private types mentioned in the question, the RM does
not specify whether the underlying type is tagged, nor whether the
equality operator is truly user-defined (as opposed to just being the
normal bit-wise equality).

It is important that the composability of "=" for these types be defined
by the language.  We choose to make them composable.  An implementation
can achieve this by making the full type tagged.  Alternatively, the
implementation could simply use the predefined "=" for these types.
(Alternatively, an implementation could treat these types specially,
making them untagged, but with composable equality.  However, this would
add some complexity to the compiler.)

Here is an analysis of implementation concerns for each type in
question:

    - System.Address: The intent is for this type to directly represent 
      a hardware address.  Therefore, it is probably not feasible to
      to implement it as a tagged type.  The simplest implementation of
      equality of Addresses is thus the normal bit-wise equality.  This
      is what most users would expect, anyway.

      On certain segmented architectures, it is possible for two
      different addresses to point to the same location.  The same thing
      can happen due to memory mapping, on many machines.  Such
      addresses will typically compare unequal, despite the fact that
      they point to the same location.

    - Ada.Strings.Maps.Character_Set: A typical implementation will use
      an array of Booleans, so bit-wise equality will be used, so it
      will compose.

    - Ada.Strings.Bounded.Generic_Bounded_Length.Bounded_String: Two
      reasonable implementations are: (1) Nul-out the unused
      characters, and use bit-wise equality, and (2) use a tagged type
      with a user-defined equality.  Either way, equality will compose.
      This is, admittedly, a slight implementation burden, because it
      rules out an untagged record with user-defined equality.

    - Ada.Strings.Unbounded.Unbounded_String: A tagged (controlled) type
      will normally be necessary anyway, for storage reclamation.  In a
      garbage-collected implementation, a tagged type is not strictly
      necessary, but we choose to require composability anyway.

    - Ada.Strings.Wide_Maps.Wide_Character_Set: Some sort of data
      structure built out of access types is necessary anyway, so the
      extra overhead of composability is not a serious problem; the
      implementation can simply make the full type tagged.

    - Ada.Task_Identification.Task_ID: This will typically be a
      pointer-to-TCB of some sort (access-to-TCB, or
      index-into-table-of-TCB's).  In any case, bit-wise equality will
      work, so equality will compose.

As to the second question, the RM clearly does not define any order of
calling "=" on components, nor does it say whether the results are
combined with "and" or "and then".  Equality operators with side effects
are questionable in any case, so we allow implementations freedom to do
what is most convenient and/or most efficient.  Consider equality of a
variant record: The implementation might first check that the
discriminants are equal, and if not, skip the component-by-component
comparison.  Alternatively, the implementation might first compare the
common elements, and *then* check the discriminants.  A third
possibility is to first compare some portions with a bit-wise equality,
and then (conditionally) call user-defined equality operators on the
other components.  All of these implementations are valid.

!appendix 97-03-19

...




^ permalink raw reply	[relevance 3%]

* Re: Constrained Character Subtype
    1997-03-13  0:00  4%   ` Robert Dewar
@ 1997-03-13  0:00  4%   ` Jeff Carter
  1 sibling, 0 replies; 132+ results
From: Jeff Carter @ 1997-03-13  0:00 UTC (permalink / raw)



Matthew Heaney wrote:
> You need some kind of set, because you're looking for some kind of testing
> membership.
> 
> There's a low-level way of implementing a set in Ada, by using a array of
> booleans:

Or you could use Ada.Strings.Maps.Character_Set;
-- 
Jeff Carter
Innovative Concepts, Inc.

Now go away, or I shall taunt you a second time.

Unsolicited commercial e-mail will be invoiced at $500 per piece.




^ permalink raw reply	[relevance 4%]

* Re: Constrained Character Subtype
  @ 1997-03-13  0:00  4%   ` Robert Dewar
  1997-03-13  0:00  4%   ` Jeff Carter
  1 sibling, 0 replies; 132+ results
From: Robert Dewar @ 1997-03-13  0:00 UTC (permalink / raw)



<<an incomplete version of this post got sent accidentally by noise on the
  line, I will cancel it, but if you see it, ignore it>>

Matthew Heany posts a longish note on how to deal with sets of characters.
I won't quote it, because it misses the very obvious answer:

  Sets of characters are a predefined feature in Ada 95!!!

Look up type Ada.Strings.Maps.Character_Set

a complete set of constructors, and functions to manipulate and provide
these sets is provided.

You can easily create the set Vowels using the To_Set operation, and
test for membership using the Is_In function.





^ permalink raw reply	[relevance 4%]

* Re: How to do case conversion?
  1996-08-10  0:00  4% How to do case conversion? Mike Shen
  1996-08-11  0:00  5% ` Robert Dewar
  1996-08-11  0:00  0% ` David C. Hoos, Sr.
@ 1996-08-13  0:00  4% ` Robert I. Eachus
  2 siblings, 0 replies; 132+ results
From: Robert I. Eachus @ 1996-08-13  0:00 UTC (permalink / raw)



In article <320D5A34.41C67EA6@cs.cmu.edu> Mike Shen <mshen+@cs.cmu.edu> writes:

  > I am trying to do case conversion in GNAT. Does anyone
  > know a simple way to do it? I expected the Ada.Strings(.Maps)
  > package to provide something for my purpose, but it doesn't.

    Others have posted the right place to look.  However, if you are
dealing with multi-lingual or non-Latin1 text be warned.

    The "correct" mapping for ISO Latin 1, which is what you should
get, may not be what you want.  In particular PC-Compatible machines,
Macintoshes, and Unix machines do not use Latin1 by default.  (The
Amiga I am typing this on does. ;-)

    The multilingual problems can arise either due to use of say
Latin2, or be more subtle.  For instance, the correct upper/lower case
mapping for e-acute in French is locale specific.

    All this is why the facilities for making your own maps are there.

--

					Robert I. Eachus

with Standard_Disclaimer;
use  Standard_Disclaimer;
function Message (Text: in Clever_Ideas) return Better_Ideas is...




^ permalink raw reply	[relevance 4%]

* Re: How to do case conversion?
  1996-08-10  0:00  4% How to do case conversion? Mike Shen
@ 1996-08-11  0:00  5% ` Robert Dewar
  1996-08-11  0:00  0% ` David C. Hoos, Sr.
  1996-08-13  0:00  4% ` Robert I. Eachus
  2 siblings, 0 replies; 132+ results
From: Robert Dewar @ 1996-08-11  0:00 UTC (permalink / raw)



Mike Shen said

"I am trying to do case conversion in GNAT. Does anyone
know a simple way to do it? I expected the Ada.Strings(.Maps)
package to provide something for my purpose, but it doesn't."

Well this is an Ada 95 question, not a GNAT question. The standard
library routine Ada.Strings.Maps.Constants has exactly what you need,
and what you might consider is how next time you can find that more
easily than having to wait for someone to reply to you on a newsgroup.
A simple method I find useful (you can obviously do better with fancy
tools) is simply to grab a copy of the ASCII version of the RM, and 
search it with your favorite editor.

I happened to know the answer to that question off the top of my head,
but if I had not, I would have searched for Lower_Case, and found the
reference in the RM almost immediately.





^ permalink raw reply	[relevance 5%]

* Re: How to do case conversion?
  1996-08-11  0:00  0% ` David C. Hoos, Sr.
@ 1996-08-11  0:00  5%   ` Robert Dewar
  0 siblings, 0 replies; 132+ results
From: Robert Dewar @ 1996-08-11  0:00 UTC (permalink / raw)



David Hoos points out that Ada.Characters.Handling contains ready made
routines that use the maps in Ada.Strings.Maps.Constants, and yes, you
may as well use them if they fit. The coding is quite trivial:

   function To_Lower (Item : in Character) return Character is
   begin
      return Value (Lower_Case_Map, Item);
   end To_Lower;

   function To_Lower (Item : in String) return String is
      Result : String (1 .. Item'Length);

   begin
      for J in Item'Range loop
         Result (J - (Item'First - 1)) := Value (Lower_Case_Map, Item (J));
      end loop;

      return Result;
   end To_Lower;

It is Lower_Case_Map that is the difficult part! Note that in Ada 95 days
it is better if you can to always use this map rather than the old 
add/subtract 32 ASCII trick, since that way your code work fine for
all Latin-1 letters without any extra effort on your part, and indeed
in an implementation with localizations of these packages for other
Latin sets, your code will still work.





^ permalink raw reply	[relevance 5%]

* Re: How to do case conversion?
  1996-08-10  0:00  4% How to do case conversion? Mike Shen
  1996-08-11  0:00  5% ` Robert Dewar
@ 1996-08-11  0:00  0% ` David C. Hoos, Sr.
  1996-08-11  0:00  5%   ` Robert Dewar
  1996-08-13  0:00  4% ` Robert I. Eachus
  2 siblings, 1 reply; 132+ results
From: David C. Hoos, Sr. @ 1996-08-11  0:00 UTC (permalink / raw)



Hi Mike,
The standard package Ada.Characters.Handling has subprograms To_Lower, and
To_Upper, for both characters and strings.
Hope this helps 
David C. Hoos, Sr.,
http://www.dbhwww.com
http://www.ada95.com

Mike Shen <mshen+@cs.cmu.edu> wrote in article
<320D5A34.41C67EA6@cs.cmu.edu>...
> I am trying to do case conversion in GNAT. Does anyone
> know a simple way to do it? I expected the Ada.Strings(.Maps)
> package to provide something for my purpose, but it doesn't.
> 
> Thanks in advance.
> 
> -Mike Shen
> 




^ permalink raw reply	[relevance 0%]

* How to do case conversion?
@ 1996-08-10  0:00  4% Mike Shen
  1996-08-11  0:00  5% ` Robert Dewar
                   ` (2 more replies)
  0 siblings, 3 replies; 132+ results
From: Mike Shen @ 1996-08-10  0:00 UTC (permalink / raw)



I am trying to do case conversion in GNAT. Does anyone
know a simple way to do it? I expected the Ada.Strings(.Maps)
package to provide something for my purpose, but it doesn't.

Thanks in advance.

-Mike Shen




^ permalink raw reply	[relevance 4%]

* Re: Differences between RM 5.0 and 6.0
  @ 1995-03-22 15:02  4% ` Norman H. Cohen
  0 siblings, 0 replies; 132+ results
From: Norman H. Cohen @ 1995-03-22 15:02 UTC (permalink / raw)


In article <Mats.Weber-2003952132250001@mlma11.matrix.ch>,
Mats.Weber@matrix.ch (Mats Weber) writes: 

|> I have a paper copy of version 5.0 of the Ada 95 RM. Can I use it safely

Only if you keep it away from an open flame.

|> or are there many changes from 5.0 to 6.0 (the standard) ?

But seriously, folks:  Changes include the treatment of children of
generics, the addition of predefined packages like Ada.Integer_Text_IO,
and changing Ada.Strings.Constants to Ada.Strings.Maps.Constants.  At
least the first two of these changes occurred after version 5.7.

Since you are already familiar with the general shape of Ada 95, I
presume you want to use the RM as a reference to look up details, so I
would definitely suggest getting the final version.

--
Norman H. Cohen    ncohen@watson.ibm.com



^ permalink raw reply	[relevance 4%]

Results 1-132 of 132 | reverse | options above
-- pct% links below jump to the message on this page, permalinks otherwise --
1995-03-20 20:32     Differences between RM 5.0 and 6.0 Mats Weber
1995-03-22 15:02  4% ` Norman H. Cohen
1996-08-10  0:00  4% How to do case conversion? Mike Shen
1996-08-11  0:00  5% ` Robert Dewar
1996-08-11  0:00  0% ` David C. Hoos, Sr.
1996-08-11  0:00  5%   ` Robert Dewar
1996-08-13  0:00  4% ` Robert I. Eachus
1997-03-12  0:00     Constrained Character Subtype Tracy Fletcher
1997-03-12  0:00     ` Matthew Heaney
1997-03-13  0:00  4%   ` Robert Dewar
1997-03-13  0:00  4%   ` Jeff Carter
1997-04-21  0:00     Equality operator overloading in ADA 83 Manuel Wenger
1997-04-22  0:00     ` Matthew Heaney
1997-04-22  0:00       ` Mats Weber
1997-04-22  0:00  3%     ` Robert A Duff
1997-06-19  0:00     What's Pure for Dist Sytems? Dale Stanbrough
1997-06-19  0:00     ` Andre Spiegel
1997-06-20  0:00       ` Robert Dewar
1997-06-24  0:00  6%     ` Andre Spiegel
1997-07-02  0:00  6% Standard library and distributed systems Andre Spiegel
1997-07-02  0:00  4% ` Tucker Taft
1997-07-03  0:00  5%   ` Andre Spiegel
1997-07-07  0:00  4%     ` Tucker Taft
1997-09-26  0:00     How do I allocate strings of variable length at runtime? Oliver Hilgendorf
1997-09-26  0:00     ` Matthew Heaney
1997-09-29  0:00  5%   ` Marc Bejerano
1997-10-13  0:00  5% comand line arguments Marin David Condic, 561.796.8997, M/S 731-96
1998-01-05  0:00  4% general-purpose vs. domain-specific programming languages Marin David Condic, 561.796.8997, M/S 731-96
1998-04-06  0:00     String Manipulation - Help Needed Howard Davies
1998-04-05  0:00  5% ` Matthew Heaney
1998-07-08  0:00     Parsing a line into strings C N
1998-07-08  0:00     ` Samuel Tardieu
1998-07-08  0:00       ` C N
1998-07-09  0:00         ` Dmitriy Anisimkov
1998-07-08  0:00           ` Brian Rogoff
1998-07-08  0:00             ` Robert Dewar
1998-07-09  0:00  5%           ` Brian Rogoff
1998-07-11  0:00  6% ` david.c.hoos.sr
1998-08-08  0:00     Why C++ is successful Jeffrey C. Dege
     [not found]     ` <35f51e53.48044143@ <m3af4mq7f4 <35EDC648.76F03F32@draper.com>
1998-09-03  0:00       ` Software landmines (loops) Patrick Doyle
1998-09-03  0:00         ` Tim McDermott
1998-09-04  0:00           ` Matthew Heaney
1998-09-08  0:00             ` Tim McDermott
1998-09-17  0:00               ` Matthew Heaney
1998-09-18  0:00  5%             ` Robert I. Eachus
1998-09-17  0:00     cookies Lisa Winkworth
1998-09-17  0:00  3% ` cookies Pascal Obry
1999-06-10  0:00     DOS/Win95 file names fluffy_pop
1999-06-11  0:00     ` Gautier
1999-06-11  0:00       ` fluffy_pop
1999-06-11  0:00  4%     ` dennison
1999-06-11  0:00  0%       ` fluffy_pop
1999-06-11  0:00  4%       ` Robert Dewar
2000-01-15  0:00     parsing a string Paolo M. Pumilia
2000-01-15  0:00     ` James S. Rogers
2000-01-24  0:00       ` pumilia
2000-01-24  0:00  4%     ` Stephen Leake
2000-01-26  0:00  0%       ` CONTRAINT ERROR (was Re: parsing a string) pumilia
2000-01-26  0:00  0%         ` Roger Racine
2001-02-22 11:01     Regex and/or LaTeX Adrian Knoth
2001-02-24  2:59     ` Rajagopalan Srinivasan
2001-02-24 15:36       ` Adrian Knoth
2001-02-26 11:41  6%     ` Lutz Donnerhacke
2001-02-26 11:48  6%     ` Lutz Donnerhacke
2001-08-21  7:27     String manupulation Reinert Korsnes
2001-08-21 18:04     ` Randy Brukardt
2001-08-22  8:15  6%   ` Reinert Korsnes
2001-08-22 15:53  6%     ` Ted Dennison
2001-08-22 16:23  4%       ` David C. Hoos
2001-08-23  8:21             ` Reinert Korsnes
2001-08-23 12:46  6%           ` David C. Hoos
2001-08-23 12:15  6% String manupulation (again) - free software Reinert Korsnes
2001-09-07  8:16     avl tree - booch components Tony Gair
2001-09-10 21:52  5% ` Jeffrey D. Cherry
2001-09-10 21:53  5% ` Jeffrey D. Cherry
2001-10-30 22:16  4% I'm baffled Wes Groleau
2001-10-30 22:39  4% baffled ANH_VO
2001-12-13  3:23     List Container Strawman 1.4 Ted Dennison
2001-12-13 23:02     ` Nick Roberts
2001-12-14 15:19       ` Ted Dennison
2001-12-15  1:20  2%     ` Nick Roberts
2001-12-15 20:29  0%       ` Ted Dennison
2001-12-16 18:45  0%         ` Nick Roberts
2001-12-24 13:52     Newbie question Jasbinder S  Uppal
2001-12-24 20:06     ` Michal Nowak
2001-12-24 21:13       ` martin.m.dowie
2001-12-25 12:36         ` Michal Nowak
2001-12-27 14:25           ` Alfred Hilscher
2001-12-29 21:54             ` Michal Nowak
2001-12-31 17:51               ` Jasbinder S Uppal
2002-01-01 21:26  6%             ` Michal Nowak
2002-05-19 15:15     Tokens ProLogic
2002-05-19 16:32     ` Tokens Pascal Obry
2002-05-19 21:48       ` Tokens ProLogic
2002-05-19 23:13  6%     ` An example was Tokens chris.danx
2002-05-19 23:30           ` chris.danx
2002-05-20  3:44  6%         ` David C. Hoos, Sr.
2002-05-20  1:36  0%       ` ProLogic
2002-06-02 16:07     config files proposal Stephen Leake
2002-06-02 21:29     ` Darren New
2002-06-02 22:16       ` Stephen Leake
2002-06-03 14:56         ` Ted Dennison
2002-06-03 16:08           ` Darren New
2002-06-04 19:55  5%         ` Ted Dennison
2002-06-09 20:43  0%           ` Stephen Leake
2002-07-18 13:05     Subtypes with Combined Ranges David Rasmussen
2002-07-18 13:15  4% ` Lutz Donnerhacke
2002-07-30  6:32     FAQ and string functions Oleg Goodyckov
2002-07-30 13:48     ` Ted Dennison
2002-07-31  7:46       ` Oleg Goodyckov
2002-07-31  9:04  6%     ` Lutz Donnerhacke
2002-09-26 17:52  4% Overloading one instance of a dispatching function Vincent Smeets
2002-11-12 19:33     how to parse words from a string Sarah Thomas
2002-11-14  2:10     ` Chad R. Meiners
2002-11-14  2:40       ` Caffeine Junky
2002-11-14  3:09         ` sk
2002-11-14  5:31           ` Dennis Lee Bieber
2002-11-14 13:40  5%         ` Sarah Thomas
2002-11-14 14:56  6%           ` David C. Hoos
2002-11-18 20:41     how to check if a string variable contains a number or string? Sarah Thomas
2002-11-19  3:19  6% ` SteveD
2002-11-26 21:41  6% Character Sets Robert C. Leif
2002-11-27  9:00  0% Grein, Christoph
2002-11-28 17:53  3% Robert C. Leif
2002-11-28 18:08     Character Sets (plain text police report) Warren W. Gay VE3WWG
2002-11-29 20:37  3% ` Robert C. Leif
     [not found]     <mailman.12.1044286941.3911.comp.lang.ada@ada.eu.org>
2003-02-04  3:37  5% ` Base 12 Integer IO Steve
     [not found]     <666191F6.00B406DF.0015D3EC@netscape.net>
2003-06-05 15:16  3% ` visibility David C. Hoos
2003-06-07  8:21  5% Visibility And838N
     [not found]     <009C830A.36D4A463.0015D3EC@netscape.net>
2003-06-07 12:18  0% ` Visibility David C. Hoos, Sr.
2003-06-27 13:25     conversion Robert I. Eachus
2003-06-27 18:42  6% ` conversion tmoran
2003-11-08 19:40     Clause "with and use" Russ
2003-11-11  8:57     ` Vinzent 'Gadget' Hoefler
2003-11-11 20:35       ` Russ
2003-11-11 22:08         ` Vinzent 'Gadget' Hoefler
2003-11-11 22:20           ` Gautier Write-only
2003-11-11 22:38             ` Vinzent 'Gadget' Hoefler
2003-11-13  7:26               ` Russ
2003-11-13 19:59                 ` Chad R. Meiners
2003-11-14  5:45                   ` Russ
2003-11-14  7:51                     ` Chad R. Meiners
2003-11-14 23:23                       ` Russ
2003-11-15 15:19                         ` Robert I. Eachus
2003-11-15 16:15  4%                       ` Gautier Write-only
2003-11-16  0:02  5%                         ` Robert I. Eachus
2003-12-11 22:01     Word counting wave
2003-12-11 22:45  5% ` David C. Hoos
2004-01-07 17:29     URGENT: inserting words into an array Qas
2004-01-07 19:48     ` Pascal Obry
2004-01-09 23:34  4%   ` Craig Carey
2004-02-26 14:17     types and non-contigous ranges Erlo Haugen
2004-02-26 16:07  5% ` Dmitry A. Kazakov
2004-02-27  7:53  0%   ` Erlo Haugen
2004-02-27 23:59  4%     ` Randy Brukardt
2004-03-01  8:50  0%       ` Erlo Haugen
2004-07-15 13:20     questions from a newbie zork
2004-07-15 13:45  5% ` Steve
2004-07-15 14:44  5% ` Georg Bauhaus
2004-08-13  5:23     character matching John J
2004-08-15 12:36     ` John J
2004-08-15 17:21  4%   ` Steve
2004-10-21 17:52  6% variable lenght strings fabio de francesco
2004-10-21 22:42     ` Marius Amado Alves
2004-10-21 23:14       ` Matthew Heaney
2004-10-22  7:38  5%     ` Martin Krischik
2004-10-21 23:05  0% ` Stephen Leake
2004-10-29 12:46     Question about Ada.Unchecked_Conversion Eric Jacoboni
2004-10-29 14:22  6% ` Dmitry A. Kazakov
2004-10-29 15:15  6% ` Nick Roberts
2004-11-11  3:33     Float to String Steve
2004-11-11  7:51     ` tmoran
2004-11-11 12:32       ` Pascal Obry
2004-11-11 15:53  5%     ` David C. Hoos, Sr.
2004-11-11 17:36  0%       ` Jeffrey Carter
2004-11-12  0:01  0%         ` David C. Hoos, Sr.
2005-03-19 16:22     Ada bench Pascal Obry
2005-03-19 16:55     ` Dr. Adrian Wrigley
2005-03-19 21:32       ` Michael Bode
2005-03-20  9:20         ` Pascal Obry
2005-03-21 23:27           ` Georg Bauhaus
2005-03-22  1:16             ` Ada bench : count words Marius Amado Alves
2005-03-22 10:59               ` Dmitry A. Kazakov
2005-03-22 11:57                 ` Marius Amado Alves
2005-03-22 12:17                   ` Dmitry A. Kazakov
2005-03-22 12:47                     ` Marius Amado Alves
2005-03-22 13:08                       ` Dmitry A. Kazakov
2005-03-22 16:48                         ` Marius Amado Alves
2005-03-22 17:34                           ` Dmitry A. Kazakov
2005-03-27 20:14                             ` jtg
2005-03-27 21:22                               ` Dmitry A. Kazakov
2005-03-28 19:54                                 ` jtg
2005-03-28 20:56                                   ` Dmitry A. Kazakov
2005-03-29 12:40                                     ` jtg
2005-04-01 20:58  5%                                   ` Georg Bauhaus
2005-03-22 19:39  6% is something wrong with is_subset?! spambox
2005-03-22 20:03  0% ` Ludovic Brenta
2005-03-22 20:11  0% ` Georg Bauhaus
2005-07-01  1:22     Data table text I/O package? Randy Brukardt
2005-07-01  3:01     ` Alexander E. Kopilovich
2005-07-02  1:54  5%   ` Randy Brukardt
2005-07-02 10:24  0%     ` Dmitry A. Kazakov
2005-07-06 22:04  0%       ` Randy Brukardt
2005-09-27  6:27     String filtering David Trudgett
2005-09-27  7:38     ` Jacob Sparre Andersen
2005-09-27  9:13  5%   ` David Trudgett
2005-09-27  9:49  0%     ` Dmitry A. Kazakov
2005-09-27 11:15  0%       ` David Trudgett
2005-09-27 14:08  6%         ` Georg Bauhaus
2006-09-17 21:03     programming question . . lakeoftea
2006-09-17 23:12  4% ` Martin
2006-10-21  1:02  5% gnat: can't find package Tim Rowe
2006-10-21  2:57  0% ` Anh Vo
2006-10-21  6:17  0% ` Jeffrey R. Carter
2006-10-21 17:03  0%   ` Tim Rowe
2006-10-21 17:54  0%     ` Tim Rowe
2006-11-15 22:00     Char type verification KE
2006-11-15 21:57  5% ` Georg Bauhaus
2006-11-15 23:15  0%   ` KE
2007-04-02  6:13     STORAGE_ERROR : EXCEPTION_STACK_OVERFLOW andrew.carroll
2007-04-02 10:10     ` Stephen Leake
2007-04-02 14:11  3%   ` andrew.carroll
2007-04-28  5:03     Reading and writing a big file in Ada (GNAT) on Windows XP Fionn Mac Cumhaill
2007-05-02  7:46     ` george
2007-05-03  6:31       ` Fionn Mac Cumhaill
2007-05-03 20:00         ` Simon Wright
2007-05-04  6:53           ` Alternative Index implementation? (Was: Reading and writing a big file in Ada (GNAT) on Windows XP) Jacob Sparre Andersen
2007-05-04  7:41             ` Dmitry A. Kazakov
2007-05-04  9:16               ` Copying string slices before calling subroutines? (Was: Alternative Index implementation?) Jacob Sparre Andersen
2007-05-04  9:44                 ` Copying string slices before calling subroutines? Jacob Sparre Andersen
2007-05-04 10:14                   ` Dmitry A. Kazakov
2007-05-04 12:07                     ` Jeffrey Creem
2007-05-04 22:27  7%                   ` Simon Wright
2007-05-05  7:33  0%                     ` Jacob Sparre Andersen
2007-05-05  7:41  0%                     ` Dmitry A. Kazakov
2007-10-21 19:15     Range types Christos Chryssochoidis
2007-10-21 20:23     ` Niklas Holsti
2007-10-21 21:28       ` Christos Chryssochoidis
2007-10-22  7:23  4%     ` Jacob Sparre Andersen
2007-10-22 11:14  0%       ` Christos Chryssochoidis
2007-10-23 23:52  0%         ` anon
2007-10-24 12:57  0%           ` Christos Chryssochoidis
2008-03-30 17:13  5% ANN: Some updates Dmitry A. Kazakov
2008-07-22  8:00     ANN: Basil -- Internet Message (email) and MIME library for Ada v 1.0 google1
2008-07-22 11:01     ` Ludovic Brenta
2008-07-22 16:35       ` google1
2008-07-22 17:19         ` Ludovic Brenta
2008-07-22 19:43           ` google1
2008-07-23 11:07             ` Ludovic Brenta
2008-07-23 12:45               ` google1
2008-07-24 10:30                 ` Alex R. Mosteo
2008-07-24 16:53                   ` Georg Bauhaus
2008-07-24 19:13  6%                 ` Dmitry A. Kazakov
2008-07-25 11:38  0%                   ` Alex R. Mosteo
2010-12-27 18:26     An Example for Ada.Execution_Time anon
2010-12-28  2:31     ` BrianG
2010-12-29  3:10  4%   ` Randy Brukardt
2011-10-14  6:58     Why no Ada.Wide_Directories? Michael Rohan
2011-10-15  1:06     ` ytomino
2011-10-17 21:33       ` Randy Brukardt
2011-10-17 23:47         ` ytomino
2011-10-18  8:01  6%       ` Dmitry A. Kazakov
2012-02-09  1:03     Need Help On Ada95 Problem Will
2012-02-09  2:01     ` Shark8
2012-02-10  8:47  6%   ` Simon Wright
2012-03-30 18:18     Passing C-style flags to C subprograms Natasha Kerensikova
2012-03-30 19:57     ` Randy Brukardt
2012-04-02 10:40  3%   ` Natasha Kerensikova
2012-04-03  2:11     Checking to see is a string is a letter deuteros
2012-04-03  7:09  6% ` Thomas Løcke
2012-06-11 21:55     Practicalities of Ada for app development Adam Beneschan
2012-06-12 21:12     ` Nomen Nescio
2012-06-13  0:04       ` Adam Beneschan
2012-06-13  8:37  5%     ` Georg Bauhaus
2015-03-06 18:01  4% Implementing character sets for Wide_Character Martin Trenkmann
2015-06-01 13:08  4% OpenToken: Parsing Ada (subset)? Jacob Sparre Andersen
2015-06-02 22:12  3% ` Stephen Leake
2015-07-18  9:00  5% How to check if letters are in a string? Trish Cayetano
2016-09-13  8:46     Question on bounded / unbounded strings Arie van Wingerden
2016-09-14 11:23  5% ` Arie van Wingerden
2016-09-14 12:57  5% ` Arie van Wingerden
2017-09-21 18:14     Ada.Strings.Unbounded vs Ada.Containers.Indefinite_Holders Victor Porton
2017-09-21 21:30     ` AdaMagica
2017-09-22 12:16       ` Victor Porton
2017-09-22 19:25         ` Simon Wright
2017-09-22 22:15           ` Victor Porton
2017-09-23  8:09             ` Dmitry A. Kazakov
2017-09-23  9:16  5%           ` Jeffrey R. Carter
2018-03-01  0:27     CONSTRAINT ERROR? access check failed Mehdi Saada
2018-03-01  8:07     ` Niklas Holsti
2018-03-01 12:44  5%   ` Mehdi Saada
2020-12-06  8:39  4% Advent of Code Day 6 John Perry
2020-12-06 11:07  0% ` Jeffrey R. Carter
2021-08-29  9:38  3% Postcondition on Strings.Maps.To_Sequence mockturtle
2021-09-01 21:07  0% ` Stephen Leake
2023-02-22 16:34  6% wait does not perform as expected Daniel Gaudry
2023-08-13 16:16     Unifont static compiled and stack size Micah Waddoups
2023-08-14  8:07     ` Niklas Holsti
2023-08-14  8:31       ` Dmitry A. Kazakov
2023-08-14  9:25         ` Kevin Chadwick
2023-08-14  9:39  4%       ` Dmitry A. Kazakov

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