comp.lang.ada
 help / color / mirror / Atom feed
* String_Holder ?
@ 2011-12-18 12:34 Natasha Kerensikova
  2011-12-18 16:48 ` Brad Moore
                   ` (3 more replies)
  0 siblings, 4 replies; 13+ messages in thread
From: Natasha Kerensikova @ 2011-12-18 12:34 UTC (permalink / raw)


Hello,

in my few Ada projects so far, I have quite often encountered the need
of storing a string along with other information in records. So I went
for discriminants containing the string size, and putting the string
directly in the record.

This works well when there is only one or two strings, but with several
of them, or in variant records, I find it quite heavy. So I was thinking
about something like that:


type String_Holder is still to be defined;

function Hold (S : String) return String_Holder;

function To_String (Holder : String_Holder) return String;

procedure Query (Holder : String_Holder;
                 Process : not null access procedure (S : String));


I'm still unsure on what kind of type String_Holder should be (private,
tagged private or interface). It would basically be a constant-size
reference to an immutable string that is stored "somewhere".

The simplest implementation would be an Unbounded_String, though if
needed it could be improved reference counting to make assignments
cheaper, or with a hash table to deduplicate identical strings, etc.

So my question is, does it make sense to have such objects? Or am I
getting blinded by my C past, where strings are always manipulated
through a char* object?

Assuming it does make sense, am I right in thinking it's better to have
such a type, even if it's a thin wrapper around Unbounded_String,
instead of using directly Unbounded_String?

Assuming it does make sense to have a String_Holder, would it be better
to have it private, tagged private or interface?
My guess is that tagged private has no advantage over interface,
especially with a default implementation around Unbounded_String, which
doesn't need to be controlled, but then controlled extension would be
heavier. Then the choice between private and interface amounts to
whether or not it could be useful to use simultaneously several
implementations of String_Holder in the same project. I cannot think of
any project where it would be the case, so I would lean towards private,
but maybe I'm lacking imagination here.

Still under the same assumption, is the above specification sane, or am
I missing something? Query procedure is probably not absolutely
necessary, but I guess it can be occasionally useful to save a string
copy compared to To_String, and it seems to be a very small
implementation burden anyway.

Still under the same assumption, can it be useful to provide unary "+"
functions to tersely convert String_Holder to String, and maybe
vice-versa, or would it do more harm (obfuscation) than good?

And lastly, is there any trick to allow a String_Holder object or
similar to be pre-elaborable?


Thanks in advance for your insights,
Natasha



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

* Re: String_Holder ?
  2011-12-18 12:34 String_Holder ? Natasha Kerensikova
@ 2011-12-18 16:48 ` Brad Moore
  2011-12-18 20:55 ` Jeffrey Carter
                   ` (2 subsequent siblings)
  3 siblings, 0 replies; 13+ messages in thread
From: Brad Moore @ 2011-12-18 16:48 UTC (permalink / raw)


On 18/12/2011 5:34 AM, Natasha Kerensikova wrote:
> Hello,
>
> in my few Ada projects so far, I have quite often encountered the need
> of storing a string along with other information in records. So I went
> for discriminants containing the string size, and putting the string
> directly in the record.
>
> This works well when there is only one or two strings, but with several
> of them, or in variant records, I find it quite heavy. So I was thinking
> about something like that:
>
>
> type String_Holder is still to be defined;
>
> function Hold (S : String) return String_Holder;
>
> function To_String (Holder : String_Holder) return String;
>
> procedure Query (Holder : String_Holder;
>                   Process : not null access procedure (S : String));
>
>
> I'm still unsure on what kind of type String_Holder should be (private,
> tagged private or interface). It would basically be a constant-size
> reference to an immutable string that is stored "somewhere".
>
> The simplest implementation would be an Unbounded_String, though if
> needed it could be improved reference counting to make assignments
> cheaper, or with a hash table to deduplicate identical strings, etc.
>
> So my question is, does it make sense to have such objects? Or am I
> getting blinded by my C past, where strings are always manipulated
> through a char* object?

Ada 2012 is in fact introducing a generic holder container.
You may want to have a look at;

http://www.ada-auth.org/standards/12rm/html/RM-A-18-18.html

>
> Assuming it does make sense, am I right in thinking it's better to have
> such a type, even if it's a thin wrapper around Unbounded_String,
> instead of using directly Unbounded_String?
>
> Assuming it does make sense to have a String_Holder, would it be better
> to have it private, tagged private or interface?

tagged private would allow more flexibility over private, since you can
extend the type to suit other purposes. Interfaces cannot have any 
components, and if you are thinking of a specific implementation such as
wrapping the unbounded string, then probably tagged private better
suits your needs since you can define the holder object to contain an
unbounded string object.


> And lastly, is there any trick to allow a String_Holder object or
> similar to be pre-elaborable?


The proposed holder container is a Remote_Types package which by
definition is preelaborable.

There shouldn't need to be any tricks. Ada.Strings.Unbounded has pragma 
Preelaborate. You should be able to do the same with your holder 
package, so long as that package does not "with" other packages that are
not preelaborable, and your package satisfies the rules for a 
preelaborated package.

Brad



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

* Re: String_Holder ?
  2011-12-18 12:34 String_Holder ? Natasha Kerensikova
  2011-12-18 16:48 ` Brad Moore
@ 2011-12-18 20:55 ` Jeffrey Carter
  2011-12-18 23:08   ` Natasha Kerensikova
  2011-12-19 11:12 ` Martin
  2011-12-19 23:53 ` Randy Brukardt
  3 siblings, 1 reply; 13+ messages in thread
From: Jeffrey Carter @ 2011-12-18 20:55 UTC (permalink / raw)


On 12/18/2011 05:34 AM, Natasha Kerensikova wrote:
>
> in my few Ada projects so far, I have quite often encountered the need
> of storing a string along with other information in records. So I went
> for discriminants containing the string size, and putting the string
> directly in the record.
>
> This works well when there is only one or two strings, but with several
> of them, or in variant records, I find it quite heavy. So I was thinking
> about something like that:
>
>
> type String_Holder is still to be defined;
>
> function Hold (S : String) return String_Holder;
>
> function To_String (Holder : String_Holder) return String;
>
> procedure Query (Holder : String_Holder;
>                   Process : not null access procedure (S : String));

I see no advantage to this over Unbounded_String.

-- 
Jeff Carter
"Many times we're given rhymes that are quite unsingable."
Monty Python and the Holy Grail
57

--- Posted via news://freenews.netfront.net/ - Complaints to news@netfront.net ---



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

* Re: String_Holder ?
  2011-12-18 20:55 ` Jeffrey Carter
@ 2011-12-18 23:08   ` Natasha Kerensikova
  2011-12-19 12:14     ` Niklas Holsti
  0 siblings, 1 reply; 13+ messages in thread
From: Natasha Kerensikova @ 2011-12-18 23:08 UTC (permalink / raw)


Hello,

On 2011-12-18, Jeffrey Carter <spam.jrcarter.not@spam.not.acm.org> wrote:
> On 12/18/2011 05:34 AM, Natasha Kerensikova wrote:
>> type String_Holder is still to be defined;
>>
>> function Hold (S : String) return String_Holder;
>>
>> function To_String (Holder : String_Holder) return String;
>>
>> procedure Query (Holder : String_Holder;
>>                   Process : not null access procedure (S : String));
>
> I see no advantage to this over Unbounded_String.

Mostly having the type named after the function of objects in the
project rather than characteristics of the objects. Also allowing to
replace it more easily later on with an implementation better suited to
the function in a particular project, should the need ever arise.


Natasha



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

* Re: String_Holder ?
  2011-12-18 12:34 String_Holder ? Natasha Kerensikova
  2011-12-18 16:48 ` Brad Moore
  2011-12-18 20:55 ` Jeffrey Carter
@ 2011-12-19 11:12 ` Martin
  2011-12-19 23:53 ` Randy Brukardt
  3 siblings, 0 replies; 13+ messages in thread
From: Martin @ 2011-12-19 11:12 UTC (permalink / raw)


On Dec 18, 12:34 pm, Natasha Kerensikova <lithium...@gmail.com> wrote:
> Hello,
>
> in my few Ada projects so far, I have quite often encountered the need
> of storing a string along with other information in records. So I went
> for discriminants containing the string size, and putting the string
> directly in the record.
>
> This works well when there is only one or two strings, but with several
> of them, or in variant records, I find it quite heavy. So I was thinking
> about something like that:
>
> type String_Holder is still to be defined;
>
> function Hold (S : String) return String_Holder;
>
> function To_String (Holder : String_Holder) return String;
>
> procedure Query (Holder : String_Holder;
>                  Process : not null access procedure (S : String));
>
> I'm still unsure on what kind of type String_Holder should be (private,
> tagged private or interface). It would basically be a constant-size
> reference to an immutable string that is stored "somewhere".
>
> The simplest implementation would be an Unbounded_String, though if
> needed it could be improved reference counting to make assignments
> cheaper, or with a hash table to deduplicate identical strings, etc.
>
> So my question is, does it make sense to have such objects? Or am I
> getting blinded by my C past, where strings are always manipulated
> through a char* object?
>
> Assuming it does make sense, am I right in thinking it's better to have
> such a type, even if it's a thin wrapper around Unbounded_String,
> instead of using directly Unbounded_String?
>
> Assuming it does make sense to have a String_Holder, would it be better
> to have it private, tagged private or interface?
> My guess is that tagged private has no advantage over interface,
> especially with a default implementation around Unbounded_String, which
> doesn't need to be controlled, but then controlled extension would be
> heavier. Then the choice between private and interface amounts to
> whether or not it could be useful to use simultaneously several
> implementations of String_Holder in the same project. I cannot think of
> any project where it would be the case, so I would lean towards private,
> but maybe I'm lacking imagination here.
>
> Still under the same assumption, is the above specification sane, or am
> I missing something? Query procedure is probably not absolutely
> necessary, but I guess it can be occasionally useful to save a string
> copy compared to To_String, and it seems to be a very small
> implementation burden anyway.
>
> Still under the same assumption, can it be useful to provide unary "+"
> functions to tersely convert String_Holder to String, and maybe
> vice-versa, or would it do more harm (obfuscation) than good?
>
> And lastly, is there any trick to allow a String_Holder object or
> similar to be pre-elaborable?
>
> Thanks in advance for your insights,
> Natasha

Have you considered a "Flyweight"?

Here's an example in Ada2012 (which is soooo much easier to acheive
than in previous Ada versions).

The coffee flavour string is repeated in each order but only unique
strings are stored and each order context contains a reference to the
string.

In a real application, you'd want probably want to add finalization.

-- Martin



-- main.adb
with Applications; use Applications;
procedure Main is
   App : Application := Create;
begin
   App.Execute;
end Main;

-- applications.ads
        private with Ada.Containers.Vectors;
        private with Coffee_Orders.Flavours;
        private with Coffee_Orders.Flavours.Factories;
limited private with Coffee_Order_Contexts;
package Applications is
   type Application (<>) is tagged limited private;
   function Create return Application;
   procedure Execute (A : in out Application);
private
   use Coffee_Orders.Flavours.Factories;
   type Order is record
      Context : access Coffee_Order_Contexts.Coffee_Order_Context;
      Flavour : access Coffee_Orders.Flavours.Flavour;
   end record;
   package Order_Vectors is
      new Ada.Containers.Vectors (Natural, Order);
   type Application is tagged limited record
      Orders          : Order_Vectors.Vector;
      Flavour_Factory : Coffee_Orders.Flavours.Factories.Factory;
   end record;
   procedure Take_Orders (A       : in out Application;
                          Flavour :        String;
                          Table   :        Integer);
end Applications;

-- applications.adb
with Ada.Text_IO;            use Ada.Text_IO;
with Coffee_Order_Contexts;  use Coffee_Order_Contexts;
with Coffee_Orders.Flavours; use Coffee_Orders.Flavours;
package body Applications is
   function Create return Application is
   begin
      return Result : Application do
         null;
      end return;
   end Create;
   procedure Take_Orders (A       : in out Application;
                          Flavour :        String;
                          Table   :        Integer) is
   begin
      A.Orders.Append ((Context => new Coffee_Order_Context'(Create
(Table)),
                        Flavour =>
Flavour_Ref'(A.Flavour_Factory.Get_Flavour (Flavour))));
   end Take_Orders;
   procedure Execute (A : in out Application) is
   begin
      A.Take_Orders ("Cappuccino", 2);
      A.Take_Orders ("Cappuccino", 2);
      A.Take_Orders ("Frappe", 1);
      A.Take_Orders ("Frappe", 1);
      A.Take_Orders ("Xpresso", 1);
      A.Take_Orders ("Frappe", 897);
      A.Take_Orders ("Cappuccino", 97);
      A.Take_Orders ("Cappuccino", 97);
      A.Take_Orders ("Frappe", 3);
      A.Take_Orders ("Xpresso", 3);
      A.Take_Orders ("Cappuccino", 3);
      A.Take_Orders ("Xpresso", 96);
      A.Take_Orders ("Frappe", 552);
      A.Take_Orders ("Cappuccino", 121);
      A.Take_Orders ("Xpresso", 121);
      for Order of A.Orders loop
         Order.Flavour.Serve_Coffee (Order.Context.all);
      end loop;
      Put_Line ("Total Coffee_Flavor objects made:" & Integer'Image
(A.Flavour_Factory.Total_Flavours_Made));
   end Execute;
end Applications;

-- coffee_order_contexts.ads
package Coffee_Order_Contexts is
   type Coffee_Order_Context (<>) is tagged private;
   function Create (Table : Integer) return Coffee_Order_Context;
   function Table_No (COC : Coffee_Order_Context) return Integer;
private
   type Coffee_Order_Context is tagged record
      Table : Integer := 0;
   end record;
end Coffee_Order_Contexts;

-- coffee_order_contexts.adb
package body Coffee_Order_Contexts is
   function Create (Table : Integer) return Coffee_Order_Context is
   begin
      return Result : Coffee_Order_Context do
         Result.Table := Table;
      end return;
   end Create;
   function Table_No (COC : Coffee_Order_Context) return Integer is
   begin
      return COC.Table;
   end Table_No;
end Coffee_Order_Contexts;

-- coffee_order_contexts-vectors.ads
with Ada.Containers.Indefinite_Vectors;
package Coffee_Order_Contexts.Vectors is
   new Ada.Containers.Indefinite_Vectors (Natural,
Coffee_Order_Context);

-- coffee_orders.ads
with Coffee_Order_Contexts; use Coffee_Order_Contexts;
package Coffee_Orders is
   type Coffee_Order is interface;
   procedure Serve_Coffee (CO  : Coffee_Order;
                           COC : Coffee_Order_Context) is abstract;
end Coffee_Orders;

-- coffee_orders-flavours.ads
private with Ada.Strings.Unbounded;
        with Coffee_Order_Contexts; use Coffee_Order_Contexts;
package Coffee_Orders.Flavours is
   type Flavour (<>) is new Coffee_Order with private;
   type Flavour_Ref is access all Flavour'Class;
   function Create (Name : String) return Flavour;
   function "=" (L, R : Flavour) return Boolean;
   overriding
   procedure Serve_Coffee (F   : Flavour;
                           COC : Coffee_Order_Context);
private
   use Ada.Strings.Unbounded;
   type Flavour is new Coffee_Order with record
      Name : Unbounded_String;
   end record;
end Coffee_Orders.Flavours;

-- coffee_orders-flavours.adb
with Ada.Strings.Equal_Case_Insensitive;
with Ada.Text_IO; use Ada.Text_IO;
package body Coffee_Orders.Flavours is
   function Create (Name : String) return Flavour is
   begin
      return Result : Flavour do
         Result.Name := To_Unbounded_String (Name);
      end return;
   end Create;
   function "=" (L, R : Flavour) return Boolean is
   begin
      return Ada.Strings.Equal_Case_Insensitive (To_String (L.Name),
To_String (R.Name));
   end "=";
   procedure Serve_Coffee (F   : Flavour;
                           COC : Coffee_Order_Context) is
   begin
      Put_Line ("Serving Coffee flavor " & To_String (F.Name)
                & " to table number " & Integer'Image (COC.Table_No));
   end Serve_Coffee;
end Coffee_Orders.Flavours;

-- coffee_orders-flavours-vectors.ads
with Ada.Containers.Vectors;
package Coffee_Orders.Flavours.Vectors is
   new Ada.Containers.Vectors (Natural, Flavour_Ref);

-- coffee_orders-flavours-factories.ads
private with Ada.Containers.Indefinite_Hashed_Maps;
private with Ada.Strings.Equal_Case_Insensitive;
private with Ada.Strings.Hash_Case_Insensitive;
private with Ada.Strings.Unbounded;
package Coffee_Orders.Flavours.Factories is
   type Factory is tagged private;
   function Get_Flavour (F    : in out Factory;
                         Name :        String)
                         return not null access Flavour;
   function Total_Flavours_Made (F : Factory) return Natural;
private
   use Ada.Strings.Unbounded;
   package Maps is
     new Ada.Containers.Indefinite_Hashed_Maps (Key_Type        =>
String,
                                                Element_Type    =>
Flavour,
                                                Hash            =>
Ada.Strings.Hash_Case_Insensitive,
                                                Equivalent_Keys =>
Ada.Strings.Equal_Case_Insensitive);
   type Factory is tagged record
      Flavours : Maps.Map;
   end record;
end Coffee_Orders.Flavours.Factories;

-- coffee_orders-flavours-factories.adb
package body Coffee_Orders.Flavours.Factories is
   function Get_Flavour (F    : in out Factory;
                         Name :        String) return not null access
Flavour is
      use type Maps.Cursor;
      C : constant Maps.Cursor := F.Flavours.Find (Name);
   begin
      if C /= Maps.No_Element then
         return F.Flavours.Constant_Reference (Name).Element;
      end if;
      F.Flavours.Insert (Name, Create (Name));
      return F.Flavours.Constant_Reference (Name).Element;
   end Get_Flavour;
   function Total_Flavours_Made (F : Factory) return Natural is
   begin
      return Natural (F.Flavours.Length);
   end Total_Flavours_Made;
end Coffee_Orders.Flavours.Factories;



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

* Re: String_Holder ?
  2011-12-18 23:08   ` Natasha Kerensikova
@ 2011-12-19 12:14     ` Niklas Holsti
  0 siblings, 0 replies; 13+ messages in thread
From: Niklas Holsti @ 2011-12-19 12:14 UTC (permalink / raw)


On 11-12-19 01:08 , Natasha Kerensikova wrote:
> Hello,
>
> On 2011-12-18, Jeffrey Carter<spam.jrcarter.not@spam.not.acm.org>  wrote:
>> On 12/18/2011 05:34 AM, Natasha Kerensikova wrote:
>>> type String_Holder is still to be defined;
>>>
>>> function Hold (S : String) return String_Holder;
>>>
>>> function To_String (Holder : String_Holder) return String;
>>>
>>> procedure Query (Holder : String_Holder;
>>>                    Process : not null access procedure (S : String));
>>
>> I see no advantage to this over Unbounded_String.
>
> Mostly having the type named after the function of objects in the
> project rather than characteristics of the objects.

That is a good aim. You can reach it by deriving a type with the name 
you want:

    type Goblin_Name is new Ada.Strings.Unbounded_String;

    type ... is record
       ...
       Goblin : Goblin_Name;
       ...
    end record;

> Also allowing to
> replace it more easily later on with an implementation better suited to
> the function in a particular project, should the need ever arise.

Simple, just change the derivation, one place, one change.

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



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

* Re: String_Holder ?
  2011-12-18 12:34 String_Holder ? Natasha Kerensikova
                   ` (2 preceding siblings ...)
  2011-12-19 11:12 ` Martin
@ 2011-12-19 23:53 ` Randy Brukardt
  2011-12-22  9:08   ` Natasha Kerensikova
  3 siblings, 1 reply; 13+ messages in thread
From: Randy Brukardt @ 2011-12-19 23:53 UTC (permalink / raw)


"Natasha Kerensikova" <lithiumcat@gmail.com> wrote in message 
news:slrnjerndj.1lme.lithiumcat@sigil.instinctive.eu...
...
> Assuming it does make sense, am I right in thinking it's better to have
> such a type, even if it's a thin wrapper around Unbounded_String,
> instead of using directly Unbounded_String?

What exactly is the advantage of your Holder type over Unbounded_String 
(other than shorter operation names :-)?

   function Hold (S : String) return String_Holder; seems to be the same as 
function To_Unbounded_String. A renames would do the trick nicely.

   function To_String (Holder : String_Holder) return String; seems to be 
the same as function To_String, don't even need to rename that.

   procedure Query (Holder : String_Holder;
                 Process : not null access procedure (S : String));
       would be trivial to write in terms of To_String, and would be more 
expensive than using To_String directly.

So I don't understand the point -- and you clearly need a reason to write a 
new package here rather than using the built-in one.

                                                    Randy. 





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

* Re: String_Holder ?
  2011-12-19 23:53 ` Randy Brukardt
@ 2011-12-22  9:08   ` Natasha Kerensikova
  2011-12-22 10:08     ` Niklas Holsti
  2011-12-22 11:40     ` AdaMagica
  0 siblings, 2 replies; 13+ messages in thread
From: Natasha Kerensikova @ 2011-12-22  9:08 UTC (permalink / raw)


Hello,

On 2011-12-19, Randy Brukardt <randy@rrsoftware.com> wrote:
> "Natasha Kerensikova" <lithiumcat@gmail.com> wrote in message 
> news:slrnjerndj.1lme.lithiumcat@sigil.instinctive.eu...
> ...
>> Assuming it does make sense, am I right in thinking it's better to have
>> such a type, even if it's a thin wrapper around Unbounded_String,
>> instead of using directly Unbounded_String?
>
> What exactly is the advantage of your Holder type over Unbounded_String 
> (other than shorter operation names :-)?

As I answered somewhere else in the thread, having a name in line with
the function rather than some irrelevant (in that case) object feature.

I would rather have String_Accumulator when I'm building a string by
repeated appends, String_Holder when I'm only interested in keeping a
reference of it, String_Buffer or String_Queue when I want to append
data to be processed by some other subprogram that would retrieve it
from head, etc.

Even though they can all be implementation with Unbounded_String under
the hood, the more specific type allows better self-documentation of the
code, and hides Unbounded_String operations that are not natural for the
given function (e.g. String_Holder is supposed to reference an immutable
string, so any operation that change the underlying Unbounded_String
would break stuff).

And in case I need extra performance, for whatever measure of
performance (be it CPU usage or memory usage or latency consistency or
anything else), I can change the implementation of that specific type
without affecting any other function.

Am I missing something that would be a serious drawback for that way of
doing things?

> So I don't understand the point -- and you clearly need a reason to write a 
> new package here rather than using the built-in one.

Do I really need a reason? I tend to consider a 20-line specification
and a 30-line package body as something extremely cheap. Am I missing
something in my cost evaluation?

The alternative proposed somewhere else is:
type String_Holder is new Unbounded_String;
with subprogram renames to remove Unbounded_String-specific parts for
better abstraction.

I feel it to be about as expensive, except that there is one package for
the entire project, while the alternative is per-client-package (unless
it gets its own package), so it scales differently.

So what am I missing there?


Thanks for your insights,
Natasha



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

* Re: String_Holder ?
  2011-12-22  9:08   ` Natasha Kerensikova
@ 2011-12-22 10:08     ` Niklas Holsti
  2011-12-22 12:23       ` Simon Wright
  2011-12-23  1:26       ` Randy Brukardt
  2011-12-22 11:40     ` AdaMagica
  1 sibling, 2 replies; 13+ messages in thread
From: Niklas Holsti @ 2011-12-22 10:08 UTC (permalink / raw)


On 11-12-22 11:08 , Natasha Kerensikova wrote:
> Hello,
>
> On 2011-12-19, Randy Brukardt<randy@rrsoftware.com>  wrote:
>> "Natasha Kerensikova"<lithiumcat@gmail.com>  wrote in message
>> news:slrnjerndj.1lme.lithiumcat@sigil.instinctive.eu...
>> ...
>>> Assuming it does make sense, am I right in thinking it's better to have
>>> such a type, even if it's a thin wrapper around Unbounded_String,
>>> instead of using directly Unbounded_String?
>>
>> What exactly is the advantage of your Holder type over Unbounded_String
>> (other than shorter operation names :-)?
>
> As I answered somewhere else in the thread, having a name in line with
> the function rather than some irrelevant (in that case) object feature.
>
> I would rather have String_Accumulator when I'm building a string by
> repeated appends, String_Holder when I'm only interested in keeping a
> reference of it, String_Buffer or String_Queue when I want to append
> data to be processed by some other subprogram that would retrieve it
> from head, etc.

I think this is a good principle.

> Even though they can all be implementation with Unbounded_String under
> the hood, the more specific type allows better self-documentation of the
> code, and hides Unbounded_String operations that are not natural for the
> given function (e.g. String_Holder is supposed to reference an immutable
> string, so any operation that change the underlying Unbounded_String
> would break stuff).
>
> And in case I need extra performance, for whatever measure of
> performance (be it CPU usage or memory usage or latency consistency or
> anything else), I can change the implementation of that specific type
> without affecting any other function.
>
> Am I missing something that would be a serious drawback for that way of
> doing things?

Adding a type "on top of" Unbounded_String, with operations that are 
implemented by calling operations of Unbounded_String, can of course 
slow things down a bit, unless the additional calls are inlined. Whether 
this is a serious drawback depends on your context.

>> So I don't understand the point -- and you clearly need a reason to write a
>> new package here rather than using the built-in one.
>
> Do I really need a reason? I tend to consider a 20-line specification
> and a 30-line package body as something extremely cheap.

I agree. Unless you need to unit test everything to 100% coverage :-)

> Am I missing something in my cost evaluation?

The program may be a little harder to understand for people who are used 
to think in terms of real types rather than abstract (private) types. 
When such people see a declaration like "Var : X_Type;" they need to 
know what X_Type "really is" before they understand how Var can be used.

>
> The alternative proposed somewhere else is:
> type String_Holder is new Unbounded_String;

I think I suggested that, but there may have been others.

> with subprogram renames to remove Unbounded_String-specific parts for
> better abstraction.

I did not suggest that. I assumed that you are coding this yourself, and 
that you would use, and perhaps rename, only those operations of 
Unbounded_String that are appropriate for the derived type, and avoid 
others. But removing the other operations is more thorough and stricter. 
If this is a requirement, I too would opt for a new type that is 
implemented by means of Unbounded_String but is not derived from it, 
otherwise the number of operations to be removed could be large.

>
> I feel it to be about as expensive,

Calling an operation that a derived type inherits from an ancestor type 
does not introduce an additional layer of calls, I believe -- the call 
goes directly to the operation of the ancestor type.

> except that there is one package for
> the entire project, while the alternative is per-client-package (unless
> it gets its own package), so it scales differently.

I don't understand how the number of packages is connected to the 
question of deriving the type or creating a new type.

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



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

* Re: String_Holder ?
  2011-12-22  9:08   ` Natasha Kerensikova
  2011-12-22 10:08     ` Niklas Holsti
@ 2011-12-22 11:40     ` AdaMagica
  1 sibling, 0 replies; 13+ messages in thread
From: AdaMagica @ 2011-12-22 11:40 UTC (permalink / raw)


On 22 Dez., 10:08, Natasha Kerensikova <lithium...@gmail.com> wrote:

> Even though they can all be implementation with Unbounded_String under
> the hood, the more specific type allows better self-documentation of the
> code, and hides Unbounded_String operations that are not natural for the
> given function (e.g. String_Holder is supposed to reference an immutable
> string, so any operation that change the underlying Unbounded_String
> would break stuff).

OK, so write your spec and implement it with Unbounded_String. That
would be a good solution of your problem.

> > So I don't understand the point -- and you clearly need a reason to write a
> > new package here rather than using the built-in one.
>
> Do I really need a reason? I tend to consider a 20-line specification
> and a 30-line package body as something extremely cheap. Am I missing
> something in my cost evaluation?

No, that's not extremely cheap (if the body is not implemented with
some other proven code which in this case this would most probably be
mostly renames). You forget about unit testing, documentation, formal
qualification testing, releasing the software to the customer, and so
on.

Any line of code you write unnecessarily adds to the costs of the
whole life cycle of your code.



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

* Re: String_Holder ?
  2011-12-22 10:08     ` Niklas Holsti
@ 2011-12-22 12:23       ` Simon Wright
  2011-12-23  1:26       ` Randy Brukardt
  1 sibling, 0 replies; 13+ messages in thread
From: Simon Wright @ 2011-12-22 12:23 UTC (permalink / raw)


Niklas Holsti <niklas.holsti@tidorum.invalid> writes:

> I assumed that you are coding this yourself, and that you would use,
> and perhaps rename, only those operations of Unbounded_String that are
> appropriate for the derived type, and avoid others. But removing the
> other operations is more thorough and stricter.

Couldn't the derivation be private? (Unbounded_String is only privately
controlled, which has caused problems with GNAT in the past, but I think
those times are behind us).



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

* Re: String_Holder ?
  2011-12-22 10:08     ` Niklas Holsti
  2011-12-22 12:23       ` Simon Wright
@ 2011-12-23  1:26       ` Randy Brukardt
  2011-12-23  6:18         ` Jeffrey Carter
  1 sibling, 1 reply; 13+ messages in thread
From: Randy Brukardt @ 2011-12-23  1:26 UTC (permalink / raw)


"Niklas Holsti" <niklas.holsti@tidorum.invalid> wrote in message 
news:9lgdtoFi8U1@mid.individual.net...
> On 11-12-22 11:08 , Natasha Kerensikova wrote:
>> On 2011-12-19, Randy Brukardt<randy@rrsoftware.com>  wrote:
...
>>> What exactly is the advantage of your Holder type over Unbounded_String
>>> (other than shorter operation names :-)?
>>
>> As I answered somewhere else in the thread, having a name in line with
>> the function rather than some irrelevant (in that case) object feature.
>>
>> I would rather have String_Accumulator when I'm building a string by
>> repeated appends, String_Holder when I'm only interested in keeping a
>> reference of it, String_Buffer or String_Queue when I want to append
>> data to be processed by some other subprogram that would retrieve it
>> from head, etc.
>
> I think this is a good principle.

I personally tend to a bit less abstraction, as I mentioned earlier this 
week, there is such a thing as too much. But this is clearly personal 
preference -- there is no right or wrong answer. But...

...
>> Am I missing something that would be a serious drawback for that way of
>> doing things?
>
> Adding a type "on top of" Unbounded_String, with operations that are 
> implemented by calling operations of Unbounded_String, can of course slow 
> things down a bit, unless the additional calls are inlined. Whether this 
> is a serious drawback depends on your context.
>
>>> So I don't understand the point -- and you clearly need a reason to 
>>> write a
>>> new package here rather than using the built-in one.
>>
>> Do I really need a reason? I tend to consider a 20-line specification
>> and a 30-line package body as something extremely cheap.
>
> I agree. Unless you need to unit test everything to 100% coverage :-)
>
>> Am I missing something in my cost evaluation?

Niklas's testing joke actually was my point. The cost to write, test, and 
maintain 50 lines of code is many times that of writing, testing, and 
maintaining 0 lines of code. That's true whether you are testing to 100% 
coverage or just simple existence tests.

Back when I was starting out, there were widely quoted studies that claimed 
that programmer productivity was about 100 lines per day, no matter what 
language, tools, or targets were involved.

That seems silly (I've written several thousand lines in a day), until you 
start to think about all of the non-coding things that one has to do in a 
typical workday. After all, I've spent more than 4 hours tracking a single 
code generator bug that turned out to require one line of code to fix 
(adding an additional condition to an if statement). And there's 
documentation and meetings and customer help and backups and the occassional 
power failure -- all of which reduce the productivity.

I don't know if that number still holds or whether something has changed it 
going forward, but even if it has doubled, a 50 line package is an 
investment of 25% of a day. One imagines that time could be used for 
something else -- it's not just in a vacuum.

> The program may be a little harder to understand for people who are used 
> to think in terms of real types rather than abstract (private) types. When 
> such people see a declaration like "Var : X_Type;" they need to know what 
> X_Type "really is" before they understand how Var can be used.

It's less that than cogentive overload. You have to at least have a concept 
of what each type is before you can reason about a piece of code. Naming 
helps here, of course, but using a familar type in the intended way is even 
easier to understand.

And I guess that is my major objection: you are creating a type that adds 
nothing to the capabilities, but you are adding something additional that 
has to be understood to work on your code. Moreover, you are forcing a 
choice between these two ways (String_Holder vs. Unbounded_String), and 
reason for choosing one or the other would not be obvious. (Especially given 
that Unbounded_String's entire reason to exist is to hold strings in 
components and the like.) We always hear complaints about having multiple 
ways to do the same thing in the Ada Standard, and that applies just as well 
to your own code.

Anyway, none of these reasons are show-stoppers (it's your code after all), 
but I think it is important to remember that there is a cost to every line 
of code you write, and there had better be an offsetting benefit to that 
code. If you can't describe the benefit clearly, then put away the keyboard 
and rethink what you are doing.

(Of course, you may have a different idea of a benefit than I do.)

                                               Randy.


 





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

* Re: String_Holder ?
  2011-12-23  1:26       ` Randy Brukardt
@ 2011-12-23  6:18         ` Jeffrey Carter
  0 siblings, 0 replies; 13+ messages in thread
From: Jeffrey Carter @ 2011-12-23  6:18 UTC (permalink / raw)


On 12/22/2011 06:26 PM, Randy Brukardt wrote:
>
> Back when I was starting out, there were widely quoted studies that claimed
> that programmer productivity was about 100 lines per day, no matter what
> language, tools, or targets were involved.

Not sure where you got that. The figure I encountered, averaged over the entire 
development effort from initial requirements to acceptance testing, was one line 
of code per person hour. By that measure, 50 unnecessary lines cost 6.25 person 
days of effort.

-- 
Jeff Carter
"C++ is like giving an AK-47 to a monk, shooting him
full of crack and letting him loose in a mall and
expecting him to balance your checking account
'when he has the time.'"
Drew Olbrich
52

--- Posted via news://freenews.netfront.net/ - Complaints to news@netfront.net ---



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

end of thread, other threads:[~2011-12-23  6:18 UTC | newest]

Thread overview: 13+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2011-12-18 12:34 String_Holder ? Natasha Kerensikova
2011-12-18 16:48 ` Brad Moore
2011-12-18 20:55 ` Jeffrey Carter
2011-12-18 23:08   ` Natasha Kerensikova
2011-12-19 12:14     ` Niklas Holsti
2011-12-19 11:12 ` Martin
2011-12-19 23:53 ` Randy Brukardt
2011-12-22  9:08   ` Natasha Kerensikova
2011-12-22 10:08     ` Niklas Holsti
2011-12-22 12:23       ` Simon Wright
2011-12-23  1:26       ` Randy Brukardt
2011-12-23  6:18         ` Jeffrey Carter
2011-12-22 11:40     ` AdaMagica

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