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: set_index and and end_of_file with just a stream reference
  @ 2021-02-23 17:21  5%           ` Shark8
  0 siblings, 0 replies; 5+ results
From: Shark8 @ 2021-02-23 17:21 UTC (permalink / raw)


On Saturday, February 20, 2021 at 12:08:16 PM UTC-7, 0012com wrote:
> Okay :-) 
> what I wanted is: 
> I read an acronyme in the stream file, if good I input the adjacent record type, otherwise I would advance on the stream until the next acronyme with set_index(stream_access, index(stream_access) + composite_type_stream_size) and read the next acronyme (unbounded_string). 
> Now I just input both objects and verify the acronyme. 
> But I don't like writing an object that maybe won't be used.
Hm, what are your datatypes? Is this ONLY text, or are you able to impose your own structure?
You could have something like this:

-- Instantiated Container Packages.
Package String_Holder is new Ada.Containers.Indefinite_Holders(
       Element_Type => String,
       "="          => Ada.Strings.Equal_Case_Insensitive
      );
Package String_Map is new Ada.Containers.Indefinite_Ordered_Maps(
       "<"          => Ada.Strings.Less_Case_Insensitive,
       "="          => Ada.Strings.Equal_Case_Insensitive,
       Key_Type     => String,
       Element_Type => String
      );

-- The heart of the operating program.
With String_Holder, String_Map;
Package Acronyms is
  -- Because this is it's own type, you can put other things in the record, like a link to the place that it's defined, if needed.
  Type Initialism is new String_Holder.Holder with null record;

  Function Expand( Acronym : Initialism ) return String;
  Procedure Register( Acronym, Expansion : String );
--...
End Acronyms;

Package Body Acronyms is
    Acronym_Map : String_Map.Map;
  Procedure Register( Acronym, Expansion : String ) is
  Begin
    Acronym_Map.Insert( New_Item => Expansion, Key => Acronym );
  End Register;  

  Function Expand( Acronym : Initialism ) return String is
  Begin
    Return Acronym_Map( Acronym );
  Exception
    when others => Return Acronym; -- I forget if it's CONSTRAINT_ERROR or ASSERT_ERROR when the element is not present.
  End Expand;
End Acronyms;

-- in your main Acronym-Stream package...
-- Text_Soup is a variant record for handling portions of an acronym-expanding string; your main data-structure would probably be an Indefinite_Vector of Text_Soup'Class,
-- you might not need Input or output, depending on your usage, but for automatically expanding the initialism you'd need to use Acronyms.Expand.

    Type Text_Soup(<>) is tagged private;
    procedure Output(
       Stream : not null access Ada.Streams.Root_Stream_Type'Class;
       Item   : in Text_Soup'Class);
    function Input(
       Stream : not null access Ada.Streams.Root_Stream_Type'Class)
       return Text_Soup'Class;

   -- Other public operations.
PRIVATE
    For Text_Soup'Class'Input  use Input;
    For Text_Soup'Class'Output use Output;

Type Text_Soup(Length : Natural) is record
  case Length is
    when 0 => Acronym : Initialism;
    when others => Text : String(1..Length);
  end case;
end record;
--...


^ permalink raw reply	[relevance 5%]

* Re: Visibility issue
  @ 2020-09-17 21:47  5% ` Shark8
  0 siblings, 0 replies; 5+ results
From: Shark8 @ 2020-09-17 21:47 UTC (permalink / raw)


On Friday, September 11, 2020 at 4:37:29 AM UTC-6, Daniel wrote:
> Hello, 
> I want to use a tagged type as a link to communicate users of a library, in the way to make one part visible to them and also to hide some content that is only needed for the implementing of the library.

Here's how that's normally achieved; I've compiled the following but haven't written a testbed/driver:

-- Daniel.ads
Package Daniel with Pure is
   -- Base Interface which all API objects implement.
   Type Abstract_Base is interface;
   
   -- All common methods.
   Function As_String(Object : Abstract_Base) return String is abstract;
   
   -- All Classwide methods.
   Function Print( Object : Abstract_Base'Class ) return String;
   
   
   -- The Callback type.
   Type Callback is access
     procedure(Item : in out Abstract_Base'Class);
   
Private
   -- The classwide "Print" returns the given object's As_String result.
   Function Print( Object : Abstract_Base'Class ) return String is
      (Object.As_String);
End Daniel;

-----------------------------------------------
-- Daniel-Implementation.ads
With
Ada.Finalization,
Ada.Strings.Equal_Case_Insensitive,
Ada.Strings.Less_Case_Insensitive,
Ada.Containers.Indefinite_Ordered_Maps;

Private Package Daniel.Implementation with Preelaborate is
   -- Fwd decl.
   Type Implementation_Base(Name_Length : Positive) is tagged private;
   
   -- Implementation_Base and its descendents have a Name, that is within the
   -- private-portion of the implementation and therefore we need an accessor.
   -- Note: Name is unique and case-insensitive.
   Function Get_Name(Object: Implementation_Base'Class) Return String;

   -- Given a name, this retrieves the object; raises constraint-error if that
   -- name is not associated with an object.
   Function Make  (Name : String) return Implementation_Base'Class;
   Function Create(Name : String) return Implementation_Base;
   Function "="(Left, Right : Implementation_Base) return Boolean;
   
Private
   -- Full decl. Note, also, that this is hidden from the API package.
   Type Implementation_Base(Name_Length : Positive) is
     new Ada.Finalization.Controlled with record
      Name : String(1..Name_Length);
   End record;
   
   -- Finalization; this will remove the registered Name from the object-map.
   overriding
   procedure Finalize   (Object : in out Implementation_Base);

   -- Instantiate the package mapping Names to Objects.
   Package Name_Map is new Ada.Containers.Indefinite_Ordered_Maps(
         Key_Type     => String,
         Element_Type => Implementation_Base'Class,
         "<" => Ada.Strings.Less_Case_Insensitive,
         "=" => "="
        );
   
   -- This is the map that associates objects and their names.
   Core_Map : Name_Map.Map;
End Daniel.Implementation;

------------------------------------------------
-- Daniel-API.ads
Private With
Daniel.Implementation;

Private Package Daniel.API with Preelaborate is
   -- The base API-visable type.
   Type API_Base(<>) is new Abstract_Base with private;
   
   -- Creation functions.
   Function Create(Name : String) return API_Base;
   Function Create(Name : String; Op : Callback) return API_Base;
   
   -- Interface functions.
   Function As_String (Object :        API_Base) return String;
   Procedure Execute  (Object : in out API_Base);
Private
   -- We derive from implementation's base, and add a discriminant for the
   -- callback and another fata-field.
   Type API_Base( CBK : Callback; Length : Positive ) is
     new Daniel.Implementation.Implementation_Base( Name_Length => Length )
     and Abstract_Base with record
      A_1 : Character := 'C';
   end record;
   
   -- We raise an exception when there is no callback given.
   Function Create(Name : String) return API_Base is
     (raise Program_Error with "Callback MUST be specified.");
   
   -- Finally, we construct an object from a call to implementation's create
   -- and fill-in the missing information using an "extension aggrigate".
   Function Create(Name : String; Op : Callback) return API_Base is
     (Implementation.Create(Name) with
      CBK => Op, Length => Name'Length, others => <>);
   
End Daniel.API;

------------------------------------------------------------------------------
-- Daniel-Implementation.adb
with
Ada.Exceptions,
Ada.Finalization;

use
Ada.Finalization;

Package Body Daniel.Implementation is
   Function "=" (Left, Right : String) return Boolean
    renames Ada.Strings.Equal_Case_Insensitive;
   
   Function Get_Name(Object: Implementation_Base'Class) Return String is
     (Object.Name);

   Function Make(Name : String) return Implementation_Base'Class is
   Begin
      Return Core_Map(Name);
   Exception
      when PE : Program_Error =>
         raise Constraint_Error with Ada.Exceptions.Exception_Message(PE);
   End Make;

   Function "="(Left, Right : Implementation_Base) return boolean is
      (Left.Name = Right.Name);
   
   Function Create(Name : String) return Implementation_Base is
   begin
      Return Result : Constant Implementation_Base :=
        (Controlled with Name_Length => Name'Length, Name => Name) do
         Core_Map.Include(New_Item => Result, Key => Name);
      end return;
   end Create;
   
   Procedure Finalize(Object : in out Implementation_Base) is
   Begin
      Core_Map.Delete( Object.Name );
   End Finalize;
   
End Daniel.Implementation;

------------------------------------------------------
-- Daniel-API.adb
Package Body Daniel.API is
   Procedure Execute  (Object : in out API_Base) is
   Begin
      Object.CBK.All(Object);
   End Execute;

   Function As_String (Object : in API_Base) return String is
   Begin
      Return '(' & Object.Get_Name & ", " & Object.A_1 & ')';
   End As_String;
End Daniel.API;

^ permalink raw reply	[relevance 5%]

* Interesting containers problem.
@ 2015-04-17 13:42  5% Shark8
  0 siblings, 0 replies; 5+ results
From: Shark8 @ 2015-04-17 13:42 UTC (permalink / raw)


Ok, so let's say we have a type for Identifiers:

   SubType Identifier is String
   with Dynamic_Predicate => Is_Valid( Identifier )
     or else raise Parse_Error with "Invalid identifier: """ & Identifier & '"';
--...
   -- ACH is a rename for Ada.Characters.Handling.
   Function Is_Valid( Input: String ) return Boolean is
     ( Input'Length in Positive and then
       ACH.Is_Letter(Input(Input'First)) and then
       ACH.Is_Alphanumeric(Input(Input'Last)) and then
       (for all Ch of Input => Ch = '_' or ACH.Is_Alphanumeric(Ch)) and then
       (for all Index in Input'First..Positive'Pred(Input'Last) =>
          (if Input(Index) = '_' then Input(Index+1) /= '_')
       )
     );

And a few types for types:
   Type Data_Type is ( Integer, Float, Fixed );
   Type Variable_Data( Type_Value : Data_Type ) is
    case Type_Value is
     when Integer => Integer_Value : Standard.Integer;
     when Float   => Float_Value   : Standard.Float;
     when Fixed   => Fixed_Value   : Fixed_Type; -- Defined elsewhere.
    end case;
   end record;

Now we can define a Symbol-table using the standard containers simply with this:

  Package Symbol_Table is
    new Ada.Containers.Indefinite_Ordered_Maps(
        Key_Type     => Identifier,
        Element_Type => Variable_Data,
        "<"          => Ada.Strings.Less_Case_Insensitive,
        "="          => "="
    );

And that's all well and good; however, there is one limitation here that is revealed when you need nesting scopes -- there is, apparently, no way to define an Element_Type to feed to Indefinite_Ordered_Maps which is an instance of Indefinite_Ordered_Maps.Maps or an instance of Variable_Data (by way of a variant record; even one which is forward declared).

What would be the proper way to handle this sort of situation?

^ permalink raw reply	[relevance 5%]

* Re: Problem with generic linked list package
  @ 2014-08-10  8:22  6%                       ` Simon Wright
  0 siblings, 0 replies; 5+ results
From: Simon Wright @ 2014-08-10  8:22 UTC (permalink / raw)


Laurent <daemon2@internet.lu> writes:

> Yes indeed if Element would be a record then insert_in_order wouldn't
> work as it is. Because "<" and "=" don't exist for this type. Perhaps
> if I compared the components of the record I would but for now I don't
> see how I would do that. Problem for later when I have to use my
> package for a real program.

   type Rec is record
      B : Boolean;
      I : Integer;
   end record;
   function "<" (L, R : Rec) return Boolean is
   begin
      return L.I < R.I;
   end "<";

and similarly for "=".

I've found it's less confusing for me if I don't actually call these
functions "<", "=" but rather Less_Than, Equals. You lose the (minor)
inconvenience of being able to use the default comparison when
instantiating your generic, but gain clarity. This is presumably why we
have Ada.Strings.Less_Case_Insensitive and Equal_Case_Insensitive;
if they were called "<", "=" there could easily be ambiguity with the
default String subprograms.


^ permalink raw reply	[relevance 6%]

* Re: Ada Popularity: Comparison of Ada/Charles with C++ STL (and Perl)
  @ 2004-09-29 22:44  7%                   ` Matthew Heaney
  0 siblings, 0 replies; 5+ results
From: Matthew Heaney @ 2004-09-29 22:44 UTC (permalink / raw)


Mark Lorenzen <mark.lorenzen@ofir.dk> writes:

> After having thought about this a bit, I would say that an equivalent
> of C++s function classes is missing.
>
> If function classes were introduced, we could build pretty powerful
> algorithms traversing the different containers and f.ex. implement an
> infinite list (also called lazy list) container. Right now the
> containers only allow for a procedure to process the elements of a
> container.

Well, you can do that using the procedure, and depositing a result
somewhere prior to returning.  

For example, in the wordcount example, you need to compute a predicate
function on map cursors:

   Sort_Vector :
   declare
      function "<" (L, R : Wordcount_Maps.Cursor) return Boolean is
         Result : Boolean;

         procedure Query_L (LK : String; LN : Natural) is
            procedure Query_R (RK : String; RN : Natural) is
            begin
               if LN > RN then
                  Result := True;
               elsif LN < RN then
                  Result := False;
               else
                  Result := Ada.Strings.Less_Case_Insensitive (LK, RK);
               end if;
            end Query_R;
         begin
            Query_Element (R, Query_R'Access);
         end;
      begin
         Query_Element (L, Query_L'Access);
         return Result;
      end;

      procedure Sort is
         new Wordcount_Vectors.Generic_Sort;
   begin
      Sort (V);
   end Sort_Vector;

This does everything the a "function class" would do in C++.

The ARG is currently discussing whether to allow functions to return
anonymous access types, which would allow us to write the predicate as:

      function "<" (L, R : Wordcount_Maps.Cursor) return Boolean is
         Result : Boolean;

         LN : Natural renames Query_Element (L).all;
         LN : Natural renames Query_Element (R).all;
      begin
         if LN > RN then
            return True;
         end if;

         if LN < RN then
            return False;
         end if;

        declare
           LK : String renames Query_Key (L).all;
           RK : String renames Query_Key (R).all;
        begin
           return Ada.Strings.Less_Case_Insensitive (LK, RK);
        end;
      end "<";

Please give me a specific, concrete example of something you can do in
C++, that you believe cannot be done using the AI-302 container library.




^ permalink raw reply	[relevance 7%]

Results 1-5 of 5 | reverse | options above
-- pct% links below jump to the message on this page, permalinks otherwise --
2004-09-22  0:21     Ada Popularity: Comparison of Ada/Charles with C++ STL (and Perl) Kevin Cline
2004-09-22  8:50     ` Björn Persson
2004-09-23  8:51       ` Kevin Cline
2004-09-23 11:01         ` Georg Bauhaus
2004-09-23 16:38           ` Kevin Cline
2004-09-24  2:47             ` Matthew Heaney
2004-09-24 13:43               ` Hyman Rosen
2004-09-24 17:47                 ` Mark Lorenzen
2004-09-24 18:16                   ` Matthew Heaney
2004-09-29 19:29                     ` Mark Lorenzen
2004-09-29 22:44  7%                   ` Matthew Heaney
2014-07-28 13:26     Problem with generic linked list package Laurent
2014-07-29  8:27     ` Stephen Leake
2014-07-29 15:38       ` Laurent
2014-08-07 19:07         ` Laurent
2014-08-07 19:21           ` Adam Beneschan
2014-08-07 19:25             ` Adam Beneschan
2014-08-07 22:20               ` Laurent
2014-08-07 23:35                 ` Adam Beneschan
2014-08-08  4:42                   ` Laurent
2014-08-09 14:32                     ` Laurent
2014-08-09 18:51                       ` Shark8
2014-08-09 21:53                         ` Laurent
2014-08-10  8:22  6%                       ` Simon Wright
2015-04-17 13:42  5% Interesting containers problem Shark8
2020-09-11 10:37     Visibility issue Daniel
2020-09-17 21:47  5% ` Shark8
2021-02-20 15:26     set_index and and end_of_file with just a stream reference Mehdi Saada
2021-02-20 16:04     ` Dmitry A. Kazakov
2021-02-20 16:22       ` Mehdi Saada
2021-02-20 16:30         ` Mehdi Saada
2021-02-20 17:59           ` Dmitry A. Kazakov
2021-02-20 19:08             ` Mehdi Saada
2021-02-23 17:21  5%           ` Shark8

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