Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Suffix _T for types found good

25 views
Skip to first unread message

amado...@gmail.com

unread,
Aug 6, 2008, 10:58:18 AM8/6/08
to
I just want to offer my experience on the old issue of adding a suffix
_T to all type names.

In my experience it is good.

In a large (50KLOC) industrial experience of analysing Ada 95 source
(written by others) this convention clearly helped understanding the
source and writing test cases. This was a team work.

I started using the convention in the personal process also, and also
experienced improvement. In the personal process, I particularly like
that:

(1) I don't have to think up "good" type names that sometimes simply
do not exist; too often it is very difficult or impossible to come up
with a good pattern of names for the type, the object, the array,
etc.; with _T at least one term is removed from the equation

(2) I can promptly write things like

Index : Index_T;
procedure Proc (Index : Index_T);
etc.

For access types I have been writing _Ptr_T but I'm not 100% happy.

Regarding "_T" vs. "_Type" I am convinced the former is better but I
have to leave the advocacy for later. Or for others ;-)

Peter C. Chapin

unread,
Aug 6, 2008, 12:34:56 PM8/6/08
to
amado...@gmail.com wrote:

> Regarding "_T" vs. "_Type" I am convinced the former is better but I
> have to leave the advocacy for later. Or for others ;-)

Personally I prefer _Type. Yes it is more verbose but it follows the
convention of using fully spelled out words for things. For access types
I have used _Pointer. As in

type Integer_Pointer is access all Integer;

It mostly seems to work for me.

Niklas Holsti

unread,
Aug 6, 2008, 1:18:38 PM8/6/08
to
amado...@gmail.com wrote:
> I just want to offer my experience on the old issue of adding a suffix
> _T to all type names.
>
> In my experience it is good.

I agree.

> For access types I have been writing _Ptr_T but I'm not 100% happy.

I use _Ref (instead of _T) for access types. To remind me of
"reference semantics".

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

amado...@gmail.com

unread,
Aug 6, 2008, 1:23:01 PM8/6/08
to
On 6 Ago, 17:34, "Peter C. Chapin" <pcc482...@gmail.com> wrote:

> amado.al...@gmail.com wrote:
> > Regarding "_T" vs. "_Type" I am convinced the former is better but I
> > have to leave the advocacy for later. Or for others ;-)
>
> Personally I prefer _Type. Yes it is more verbose but it follows the
> convention of using fully spelled out words for things.

But this is not really a thing, it's a suffix :-)

> For access types
> I have used _Pointer. As in
>
>         type Integer_Pointer is access all Integer;
>
> It mostly seems to work for me.

Here I am more militant. It must end in _T or _Type also. Otherwise
you loose the advantages e.g. you cannot write

Integer_Pointer : Integer_Pointer_T;

And this is also one reason why I prefer _T to _Type (and Ptr to
Pointer): because _Pointer_Type (or even _Ptr_Type) is just too long a
suffix.

(This is one case where abbreviations are acceptable. IIRC even the
Guidelines 95 accept exceptions to the long names rule. The industry
abuses this with their way too many and unecessary 3-letter acronyms,
but this is an acceptable case.)

But this is for the application types (_T). More in house style. For
libraries I think I'd rather see _Type. More conventional. But still,
a suffix.

And in sum, whatever the form, it's good to see that more Adaists are
suffixists :-)

amado...@gmail.com

unread,
Aug 6, 2008, 1:57:15 PM8/6/08
to
"_Ref_T" has the right size :-)

But it's got to have the _T. I want to write

Object_Ref : Object_Ref_T;

Niklas Holsti

unread,
Aug 6, 2008, 2:43:44 PM8/6/08
to

I use a lot of private types, not visibly of an access type, but
privately defined as an access to a type defined in the body of the
package. I want to hide, to some extent, the fact that the type is
implemented as an access type, so I don't use _Ref on the object
identifiers. Nearly all uses of identifiers for such objects occur
as formal or actual parameters; the only reason that I use _Ref on
the type-name, instead of _T, is to explain why the parameter mode
is nearly always "in", although the parameter may be modified:

procedure Foo (Object : in Object_Ref) ...

Using _Ref on the object identifiers would reduce readability in my
opinion -- the many _Refs would clutter the statements, and not
only the declarations. I treat the _Ref suffix as reserved for
access types.

Jeffrey R. Carter

unread,
Aug 6, 2008, 3:11:36 PM8/6/08
to
amado...@gmail.com wrote:
> I just want to offer my experience on the old issue of adding a suffix
> _T to all type names.
>
> In my experience it is good.

I disagree. _T[ype] adds no value. Consider your examples:

> Index : Index_T;
> procedure Proc (Index : Index_T);

It is clear without the suffix that the identifiers are types.

Making the effort to come up with good names is an important part of SW
engineering. _T[ype] is an excuse for not thinking.

I use a number of suffices for type names to allow using the best name for
objects and parameters, while still adding value to the type name:

Numeric types: _Value, _Index, (rarely) _Range
Enumeration types (and numeric types used as IDs): _ID, _Name
Access types: _Ptr, _Handle
Private types: _Handle
Array types: _Set, _List
Record types: _Info, _Data, _Group

These suffixes provide information about the kind of type and its intended
usage. Of course, when a better name exists, it should be used rather than
unthinkingly using one of these.

On a large project with multiple developers this approach proved to be easy to
use and understand.

--
Jeff Carter
"Sheriff murdered, crops burned, stores looted,
people stampeded, and cattle raped."
Blazing Saddles
35

amado...@gmail.com

unread,
Aug 6, 2008, 3:16:37 PM8/6/08
to
> Numeric types: _Value, _Index, (rarely) _Range
> Enumeration types (and numeric types used as IDs): _ID, _Name
> Access types: _Ptr, _Handle
> Private types: _Handle
> Array types: _Set, _List
> Record types: _Info, _Data, _Group

These are wonderful afixes, thanks for sharing, I use similar afixes
myself personaly and on teams. Only, I still add _T, so I can write

Object_Value : Object_Value_T;

amado...@gmail.com

unread,
Aug 6, 2008, 3:36:09 PM8/6/08
to
> > Object_Ref : Object_Ref_T;

...
> Using _Ref on the object identifiers would reduce readability in my
> opinion -- the many _Refs would clutter the statements...

Yes, this is only for cases where you have a value and a pointer in
the same block of logic e.g.

...
Object_Ref : Object_Ref_T;
Object : Object_T;
Thing_Ref : Thing_Ref_T;
Thing : Thing_T;
declare
Object_Ref := Complicated_Logic_To_Find_An_Access_Type;
Object := Object_Ref.all;
X := Logic_Not_Dependent_On_The_Address (Object);
-- similarly for Thing
Y := Logic_Not_Dependent_On_The_Address (Thing);
Z := Logic_Not_Dependent_On_The_Addresses (Object, Thing);
-- and so on and so on

Jeffrey R. Carter

unread,
Aug 6, 2008, 3:47:50 PM8/6/08
to
amado...@gmail.com wrote:
>
> Object_Value : Object_Value_T;

If I have a type Object_Value, it's because the best object/parameter name is
not Object_Value. If the best name is Object_Value, then there is still a better
type name than unthinkingly appending _T to the best name.

Obviously this is a contrived example, but _Value is usually not the best choice
for an object/parameter name.

Pascal Obry

unread,
Aug 6, 2008, 4:06:24 PM8/6/08
to amado...@gmail.com
amado...@gmail.com a écrit :

> These are wonderful afixes, thanks for sharing, I use similar afixes
> myself personaly and on teams. Only, I still add _T, so I can write
>
> Object_Value : Object_Value_T;

I agree with Jeffrey here. Object_Value_T is just not a good name.

What object? What is value?

I prefer some descriptive names like:

Family_Name
Cover_Color
Log_Filename

I have one exception where I use Object for tagged types as I try to
design package to avoid use clause this is fine.

package SMTP is
...

package SMTP.Server is
type Object is tagged...

Wanadoo : SMTP.Server.Object;

Pascal.

--

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

Peter C. Chapin

unread,
Aug 6, 2008, 5:57:31 PM8/6/08
to
amado...@gmail.com wrote:

> Integer_Pointer : Integer_Pointer_T;

I suppose in this case I would wonder if a better name for the object
Integer_Pointer could be found.

Peter

amado...@gmail.com

unread,
Aug 6, 2008, 6:07:09 PM8/6/08
to
Object_Value was sort of meta-symbol.

Real example:

subtype Node_Index_T is Positive;
type Node_Value_T is range 1 .. 10;

type Node_T is
record
Parent : Node_Index_T;
Value : Node_Value_T;
-- ...
end record;

type Tree_T is array (Node_Index_T range <>) of Node_T;
subtype Triad_T is Tree_T (1 .. 3);

type Triad_Value_T is 1 .. 30;

-- Then down the road I need to make computations involving triad and
node values.
-- And indexes.

Triad_Value : Triad_Value_T;
Node_Value : Node_Value_T;
Node_Index : Node_Index_T;

-- See?

And even if you can come up with good different names for types and
objects, even if you magically did that effortlessly, why double the
lexicon? Can it possibly make the code better? Just to avoid a suffix
rule?

amado...@gmail.com

unread,
Aug 6, 2008, 6:14:33 PM8/6/08
to
> > Integer_Pointer : Integer_Pointer_T;
>
> I suppose in this case I would wonder if a better name for the object
> Integer_Pointer could be found.

Yes this was a poor example. See the nodes-trees-triads-values-indexes
example passim.

Jeffrey R. Carter

unread,
Aug 6, 2008, 7:11:58 PM8/6/08
to
amado...@gmail.com wrote:
>
> -- See?

No. I have no idea what you mean by a node or triad value. Maybe this is because
I'm not familiar with the domain, or maybe it's because these are not good
names, with or without _T.

> And even if you can come up with good different names for types and
> objects, even if you magically did that effortlessly, why double the
> lexicon? Can it possibly make the code better? Just to avoid a suffix
> rule?

It can certainly make the code better. The idea here is not just to avoid a
rule, but to make the code easier to read and understand. That is worth
expending extra effort on.

Presumably a node value is a value stored in a node. But the fact that values
are stored in nodes is not generally an important attribute of those values, and
so not a basis for a good name for the type.

It seems odd to me to have an explicit type stored in a node. Generally I'd
expect that to be a generic parameter, with an appropriate name:

type Node_Info is record
Parent : Node_Index;
Data : Element;
...
end record;

Or perhaps it has something to do with the implementation of the tree structure:
Depth : Depth_Value;

I can't even begin to comment on triad value.

There will always be coders who will try to avoid essential effort through
simple rules.

amado...@gmail.com

unread,
Aug 6, 2008, 7:25:08 PM8/6/08
to
The domain is problem 68 of ProjectEuler.net
Program attached.
The lexicon Node_Value, Node_Index, Triad_Value (aka line total) was
the most clear that I could think of.
I do not try to avoid essential work. I do try to avoid the
inessential and even counterproductive work of increasing the lexicon.

with Ada.Text_IO; use Ada.Text_IO;

procedure Pentagon is

-- This is my solution to problem 68 on ProjectEuler.net
-- (C) 2008 Marius Amado-Alves
-- mar...@amado-alves.info
-- marius63 on ProjectEuler.net

-- Currently this program produces the solution
-- 6 7 3 4 3 9 2 9 5 10 5 1 8 1 7
-- which is *not* accepted by ProjectEuler.net
-- Debug away!
-- 2008-08-05

-- The overall approach is to generate candidate strings in
descending order and
-- stop at the first valid pattern.

-- We establish a few theorems to reduce the set of candidate
strings.

-- Theorem 1.
-- 10 is an outer node.
-- This derives from the requirement that the solution have 16
digits.

-- Theorem 2.
-- The lowest outer number is at most 6.
-- This derives from theorem 1 and the requirement
-- that the solution start at the lowest outer node.

-- Theorem 3.
-- The possible line totals are in [14, 19].
-- This is proved later.

-- Theorem 4.
-- A sequence with 10 more to the right is greater.
-- This derives from Theorem 1, via the fact that there is always
-- at least one number bigger than 1 in any triad to the left of 10,
-- and so more triads to the left entail a higher total,
-- (because left means more significance).

-- To clarify: we give preference to higher numbers more to the left,
-- except 10 which is placed as most to the right as possible.

-- We index the nodes as follows:
--
-- (1)
-- *
-- *
-- (6) (2)
-- * * *
-- * * *
-- (10) (7)
-- * * *
-- * * *
-- (5) (9) * * (8) * * (3)
-- *
-- *
-- (4)
--
-- We assume node 1 is the lowest external node.
-- So the nodes in the sequence for the digit string are as defined
in H below.

type Node_Index_T is range 1 .. 10;
type Sequence_Index_T is range 1 .. 15;
subtype Triad_Index_T is Sequence_Index_T range 1 .. 5;

H : array (Sequence_Index_T) of Node_Index_T :=
-- triad 1 triad 2 triad 3 triad 4 triad 5
( 1, 6, 7, 2, 7, 8, 3, 8, 9, 4, 9, 10, 5, 10, 6 );
-- : :.......: :.......: :.......: :........: :
-- :................................................:

-- This convention helps prove theorem 3, as follows.
-- Clearly each external node 1,2,3,4,5 occurs exactly once,
-- and each shared node 6,7,8,9,10 occurs exactly twice, in a
sequence,
-- as illustrated above.
-- So the sum z of all values in a sequence is
--
-- z = x1 + x2 + x3 + x4 + x5 + 2 * (x6 + x7 + x8 + x9 + x10)
--
-- where xI is the value (the number) at node I.
-- Clearly the minimum and maximum values of z are
--
-- 6 + 7 + 8 + 9 + 10 + 2 * (1 + 2 + 3 + 4 + 5 ) = 70
-- 1 + 2 + 3 + 4 + 5 + 2 * (6 + 7 + 8 + 9 + 10) = 95
--
-- Also clearly each possible line total t is such that
--
-- t = z / 5
--
-- And so the minimum and maximum values of t are 14 and 19.

subtype Triad_Total_T is Natural range 14 .. 19;
subtype Node_Value_T is Natural range 1 .. 10;

type Node_T is record
Value : Node_Value_T;
Defined : Boolean;
end record;

type Solution_T is array (Node_Index_T) of Node_T;

type Precedence_T is range 1 .. 10;
W : array (Precedence_T) of Node_Value_T := (9,8,7,6,5,4,3,2,1,10);

function Img (X : Node_T) return String is
begin
if X.Defined then return Node_Value_T'Image (X.Value);
else return " *";
end if;
end;

procedure Put_Img (X : Solution_T) is
begin
for I in Sequence_Index_T loop
Put (Img (X (H(I))));
end loop;
New_Line;
end;

function Triad_Total
(Solution : Solution_T; Triad : Triad_Index_T) return
Triad_Total_T
is
I : Sequence_Index_T := Sequence_Index_T ((Triad - 1) * 3 + 1);
begin
return Triad_Total_T (Solution (H(I)).Value +
Solution (H(I + 1)).Value +
Solution (H(I + 2)).Value);
end;

procedure Find_Next_Unset_Node
(Solution : Solution_T; I : out Node_Index_T; Found : out Boolean)
is
begin
for J in Sequence_Index_T loop
if not Solution (H(J)).Defined then
I := H(J);
Found := True;
return;
end if;
end loop;
Found := False;
end;

Found : exception;

procedure Inc (X : in out Integer) is begin X := X + 1; end;

procedure Examine_Triad
(Solution : Solution_T;
Triad : Triad_Index_T;
Possibly_Partial_Total : out Natural;
Qt_Of_Defined_Nodes : out Natural)
is
I : Sequence_Index_T := Sequence_Index_T ((Triad - 1) * 3 + 1);
begin
Possibly_Partial_Total := 0;
Qt_Of_Defined_Nodes := 0;
for J in Sequence_Index_T range I .. I + 2 loop
if Solution (H(J)).Defined then
Inc (Qt_Of_Defined_Nodes);
Possibly_Partial_Total :=
Possibly_Partial_Total + Natural (Solution
(H(J)).Value);
end if;
end loop;
end;

function Legal
(Solution : Solution_T;
Triad : Triad_Index_T := 1;
Min : Triad_Total_T := 14;
Max : Triad_Total_T := 19)
return Boolean
is
I : Sequence_Index_T := Sequence_Index_T ((Triad - 1) * 3 + 1);
Val, Def : Natural;
begin
Examine_Triad (Solution, Triad, Val, Def);
if Def = 3 then
if Val < Min or Val > Max then return False;
elsif Triad = 5 then return True;
else return Legal (Solution, Triad + 1, Val, Val);
end if;
elsif Def = 2 then
if Val + 9 < Min or Val + 1 > Max then return False;
elsif Triad = 5 then return True;
else return Legal (Solution, Triad + 1, Min, Max);
end if;
elsif Def = 1 then
if Val + 1 + 2 > Max then return False;
elsif Triad = 5 then return True;
else return Legal (Solution, Triad + 1, Min, Max);
end if;
elsif Def = 0 then
if Triad = 5 then return True;
else return Legal (Solution, Triad + 1, Min, Max);
end if;
end if;
-- just to avoid no return compiler warning
raise Program_Error;
return False;
end;

Checked : Natural := 0;

procedure Check (Solution : Solution_T) is
K : Triad_Total_T;
begin
Inc (Checked);
K := Triad_Total (Solution, 1);
if Triad_Total (Solution, 2) = K and then
Triad_Total (Solution, 3) = K and then
Triad_Total (Solution, 4) = K and then
Triad_Total (Solution, 5) = K then
raise Found;
end if;
exception
when Found =>
Put_Line (Natural'Image (Checked) & " solutions checked.");
Put (" Solution:");
Put_Img (Solution);
raise;
when others => null;
end;

function Has_Value (Solution : Solution_T; X : Node_Value_T) return
Boolean is
begin
for I in Node_Index_T loop
if Solution (I).Defined and then Solution (I).Value = X then
return True; end if;
end loop;
return False;
end;

procedure Complete (Solution_In : Solution_T) is
Solution : Solution_T := Solution_In;
I : Node_Index_T;
Found : Boolean;
X : Node_Value_T;
begin
if Legal (Solution) then
Put_Img (Solution);
Find_Next_Unset_Node (Solution, I, Found);
if Found then
for Y in Precedence_T loop
X := W (Y);
if not Has_Value (Solution, X) then
Solution (I) := (Value => X, Defined => True);
Complete (Solution);
Solution (I).Defined := False;
end if;
end loop;
else
Check (Solution);
end if;
end if;
end;

Solution : Solution_T := (others => (Defined => False, others =>
<>));
begin
Solution (1).Defined := True;
for X in reverse Node_Value_T range 1 .. 6 loop
Solution (1).Value := X;
Complete (Solution);
end loop;
end;

Steve

unread,
Aug 6, 2008, 9:23:38 PM8/6/08
to
"Peter C. Chapin" <pcc4...@gmail.com> wrote in message
news:4899d2af$0$19731$4d3e...@news.sover.net...

I go with _Type too, but for pointers I go with _Acc.

For years the convention at work (I'm not sure where it came from) was to
precede type names with a lower case "a" or "an" so a declaration would be
something like:

index : anIndex;
buffer : aBuffer;

Since I used the convention for years I can say it helped readability a lot,
but every once in a while I did run into cases where I would want a variable
name to start with a or an and would have to choose something different, or
accept some "different" looking code.

Regards,
Steve


Randy Brukardt

unread,
Aug 6, 2008, 11:05:37 PM8/6/08
to
"Peter C. Chapin" <pcc4...@gmail.com> wrote in message
news:4899d2af$0$19731$4d3e...@news.sover.net...

When we designed Claw, we tried to use "_Type" consistently. Along with a
number of other standard prefixes and suffixes so that the different
packages had a consistent feel. I'm not sure we quite succeeded (we didn't
create a tool to check the names, and we probably should have).

Randy.


Jean-Pierre Rosen

unread,
Aug 7, 2008, 2:56:09 AM8/7/08
to
Randy Brukardt a écrit :

> When we designed Claw, we tried to use "_Type" consistently. Along with a
> number of other standard prefixes and suffixes so that the different
> packages had a consistent feel. I'm not sure we quite succeeded (we didn't
> create a tool to check the names, and we probably should have).
>
But of course, such a (free) tool exists now! ;-)

--
---------------------------------------------------------
J-P. Rosen (ro...@adalog.fr)
Visit Adalog's web site at http://www.adalog.fr

Georg Bauhaus

unread,
Aug 7, 2008, 3:16:04 AM8/7/08
to
amado...@gmail.com wrote:

> And even if you can come up with good different names for types and
> objects, even if you magically did that effortlessly, why double the
> lexicon? Can it possibly make the code better? Just to avoid a suffix
> rule?

Some points of reference for choosing names, collected
here and there. They are not perfect rules, but I
think they make sense:

- Can you answer the questions,
[a] "What kind of Node are these?" -> secific type
[b] "What kind of Node is this one?" -> specific object

A type in the sense of [a] comprises many things and
is possibly served well by a generic term. At first sight,
"Node" is such a term: assigning different meanings to "Node"
is easy. Too easy. It doesn't say what kind of Node.

In a given program's context, the nodes refer to some
larger thing of which they form part. This relation
may offer advice on chosing a qualification of Node.
A package name can serve as a qualifying addition.
There may even be another word that somehow includes
the notion of Node.

An object in the sense of [b] has identity. Identity is
usually designated by a locally unique specific name.
The name can allude to the specifics. "Central_Star" or
even "Sun" are possibly better names than just
"Celestial_Body" or "Node", I should think.

The identity can be a bit of a formal identity.
For example, a subprogram parameter name designates a
specific object during each invocation. But there are
many invocations. Each gets a different specific node.
In this case, a convention is to use the prefix
"The_" to indicate identity:

procedure Foo(The_Node: ....);

The name here expresses that Foo is going to deal with
just one node, namely The_Node. But when declaring
specific objects, e.g. nodes in certain roles,

Junction: ...;
Crossing: ...;


It seems to be tempting to just use some variation of
a type name for objects. Example:

osw: OutputStreamWriter; -- NOT!

is typical of programs targetting the JVM. So the reader
remembers that "osw" designates some output channel.
But which one? The programmer was too lazy to think of
a name. Points of reference: The purpose of this output.
Where does it end? Which ends does it connect?

amado...@gmail.com

unread,
Aug 7, 2008, 4:51:41 AM8/7/08
to
procedure Complex_Logic_With_An_Input_Stream_And_An_Output_Stream is
Input_Stream : Stream;
Output_Stream : Stream;
-- ...
-- OK

procedure Complex_Logic_With_Only_An_Input_Stream is
Input_Stream : Stream;
-- ...
-- Mantainer comes and says:
-- hmmm... this must mean there is also an Output_Stream
-- the logic is more complicated than I thought
-- where is the darn thing?

procedure Complex_Logic_With_Only_An_Input_Stream is
Stream : Stream_T;
-- ...
-- better
-- no dialetic doubts anymore
-- maybe a vague feeling of sadness from the poor lexicon
-- but this can be solved by putting jokes in comments :-)
-- sans impairing understandability

Georg Bauhaus

unread,
Aug 7, 2008, 6:10:17 AM8/7/08
to
amado...@gmail.com schrieb:

> procedure Complex_Logic_With_An_Input_Stream_And_An_Output_Stream is
> Input_Stream : Stream;
> Output_Stream : Stream;
> -- ...
> -- OK

The declarations say little about the streams, other than
their direction;
everything else about the streams has to be said in comments,
and later looked up in comments, thus extending the "lexicon"
way more, and less formally, than by choosing, say,

Cam_Corder: Input_Stream;
Null_Device: Output_Stream;


When they are used, another aspect appears. Compare

Temp'Write(Stream => Null_Device);

to

Temp'Write(Stream => Output_Stream);

The second line, using "Output_Stream" as an object name,
needs a back reference, as a consequence of being general.
The first line does not need this kind of lookup, I think.


> procedure Complex_Logic_With_Only_An_Input_Stream is
> Stream : Stream_T;

This anonymity does not even indicate the direction of data flow.
It can be understood only if there is nothing to
understand, which is what you will have to understand first!
;-) ;-)


--
Georg Bauhaus
Y A Time Drain http://www.9toX.de

Georg Bauhaus

unread,
Aug 7, 2008, 7:32:24 AM8/7/08
to
Georg Bauhaus schrieb:

> When they are used, another aspect appears. Compare
>
> Temp'Write(Stream => Null_Device);
>
> to
>
> Temp'Write(Stream => Output_Stream);
>

The syntax should be

Node_Info'Write(Null_Device, Temp);

vs

Node_Info'Write(Output_Stream, Temp);

Maciej Sobczak

unread,
Aug 7, 2008, 8:12:19 AM8/7/08
to
On 6 Sie, 16:58, amado.al...@gmail.com wrote:
> I just want to offer my experience on the old issue of adding a suffix
> _T to all type names.
>
> In my experience it is good.

In what way is it any better than appending suffix _V to variable
names, _P to procedures and _F to functions?

If you think that adding _V to variable names is unreasonable, you are
not alone, but if at the same time you cannot find any obvious reason
for _T in types being better than _V in variables, then the only
honest conclusion is that all such rules are equally misplaced.

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

amado...@gmail.com

unread,
Aug 7, 2008, 8:30:31 AM8/7/08
to
> In what way is it any better than appending suffix _V to variable
> names, _P to procedures and _F to functions?

You got a good theoretical point there. My practical experience only
covers _T. Maybe _P, _F etc. do not pay off. Dunno.

amado...@gmail.com

unread,
Aug 7, 2008, 8:37:12 AM8/7/08
to
>     Cam_Corder: Input_Stream;
>     Null_Device: Output_Stream;

When obvious different names exist this is fine. This concerns only
one adavantage of _T, automatic different names. The suffix helps here
in other cases, which seem to pop up often too. And then for
uniformity we append _T to all. It does not exclude proper naming.

Cam_Corder: Input_Stream_T;
Null_Device: Output_Stream_T;

And then there are the other advantages (see passim).

Dmitry A. Kazakov

unread,
Aug 7, 2008, 8:51:26 AM8/7/08
to
On Thu, 7 Aug 2008 05:12:19 -0700 (PDT), Maciej Sobczak wrote:

> If you think that adding _V to variable names is unreasonable, you are
> not alone, but if at the same time you cannot find any obvious reason
> for _T in types being better than _V in variables, then the only
> honest conclusion is that all such rules are equally misplaced.

Right, in my, admittedly radical opinion, all cases where the programmer
sees two things for which he is tempted to use the same name (but cannot!),
indicate some problem. Apart from poor design it could be a language
problem as well. Like when an entity is introduced, which should better be
anonymous or inferred.

Consider T and class T. In Ada T'Class is inferred, against the named
equivalence otherwise typical for it. One could have chosen in Ada 83
spirit:

type T is tagged ...
type T_Class is class of T;

but then one would have a problem, how to name the class of T's?

Another example:

Line : array (1..80) of Character;

no need to name the singleton's type, no problem to name that type.

I don't like _Type, _Ptr, _Ref, but I am using them. (:-))

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

Colin Paul Gloster

unread,
Aug 7, 2008, 11:10:02 AM8/7/08
to
On Wed, 6 Aug 2008, Steve wrote:

|-----------------------------------------------------------------------------|


|""Peter C. Chapin" <pcc4...@gmail.com> wrote in message |
|news:4899d2af$0$19731$4d3e...@news.sover.net... |
|> amado...@gmail.com wrote: |
|> |
|>> Regarding "_T" vs. "_Type" I am convinced the former is better but I |
|>> have to leave the advocacy for later. Or for others ;-) |
|> |
|> Personally I prefer _Type. Yes it is more verbose but it follows the |
|> convention of using fully spelled out words for things. For access types I |

|> [..] |
| |
|I go with _Type too, [..]" |
|-----------------------------------------------------------------------------|

I prefer _Type instead of _T.

|-----------------------------------------------------------------------------|


|"For years the convention at work (I'm not sure where it came from) was to |
|precede type names with a lower case "a" or "an" so a declaration would be |
|something like: |
| |
| index : anIndex; |
| buffer : aBuffer; |
| |
|Since I used the convention for years I can say it helped readability a lot, |
|but every once in a while I did run into cases where I would want a variable |
|name to start with a or an and would have to choose something different, or |
|accept some "different" looking code." |

|-----------------------------------------------------------------------------|

I do not remember having had seen this convention before. I like a
variant of it: a_buffer instead of aBuffer.

amado...@gmail.com

unread,
Aug 7, 2008, 11:37:13 AM8/7/08
to
"I don't like _Type, _Ptr, _Ref, but I am using them." (Kasakov)

This is an adage of genius that says it all!
In a perfect program all names are different and just right. No need
for _T et al.
But for some reason it is difficult to write perfect programs ;-)

Ray Blaak

unread,
Aug 7, 2008, 12:51:43 PM8/7/08
to
amado...@gmail.com writes:

I suggest:
procedure Complex_Logic_With_An_Input_Stream_And_An_Output_Stream is
Input : Stream;
Output : Stream;

With small routines, the scope of things are clear, and simple names are easy
to read and understand.

--
Cheers, The Rhythm is around me,
The Rhythm has control.
Ray Blaak The Rhythm is inside me,
rAYb...@STRIPCAPStelus.net The Rhythm has my soul.

Ray Blaak

unread,
Aug 7, 2008, 1:01:16 PM8/7/08
to
Georg Bauhaus <rm.tsoh.plus...@maps.futureapps.de> writes:
> It seems to be tempting to just use some variation of
> a type name for objects. Example:
>
> osw: OutputStreamWriter; -- NOT!
>
> is typical of programs targetting the JVM. So the reader
> remembers that "osw" designates some output channel.
> But which one? The programmer was too lazy to think of
> a name. Points of reference: The purpose of this output.
> Where does it end? Which ends does it connect?

I would use instead:

writer : OutputStreamWriter;

Use small routines. Then the names become clear, even if it is just osw.

Succinct naming as a part of the general strategy of "Spartan Programming" is
talked about here:

http://ssdl-wiki.cs.technion.ac.il/wiki/index.php/Spartan_programming

Some further debate about those ideas are found in the Coding Horror blog:

http://www.codinghorror.com/blog/archives/001148.html

At the risk of offense, being an Ada group and all, I must point out that
Java's case insensitivity allows this kind of thing:

Node node;

which in practice works just fine: types are capitalized, values are not. It's
easy to write, to read, and to maintain.

Before I get blasted about the evils of case insensitivity, I should point out
that Java is a unicode language, allows unicode in its identifiers, and case
folding is not sensical in the general case for unicode characters. With Ada
being essentially an ASCII language, the case folding debate has merit.

Ray Blaak

unread,
Aug 7, 2008, 1:04:12 PM8/7/08
to
Colin Paul Gloster <Colin_Pau...@ACM.org> writes:
> index : anIndex;
> buffer : aBuffer;

This is backwards to me:

anIndex : Index;
aBuffer : Buffer;

E.g. the value is a specific instance vs the type is general. The names should
reflect that.

amado...@gmail.com

unread,
Aug 7, 2008, 1:19:16 PM8/7/08
to
> >  index : anIndex;
> >  buffer : aBuffer;
>
> This is backwards to me:
>
>   anIndex : Index;
>   aBuffer : Buffer;
>
> E.g. the value is a specific instance vs the type is general. The names should
> reflect that.

Finally, someone said it!

Ray, on the issue of small routines, yes, *perfect* code is only
compound of small routines ;-)

amado...@gmail.com

unread,
Aug 7, 2008, 2:44:34 PM8/7/08
to
On 7 Ago, 18:19, amado.al...@gmail.com wrote:
> > >  index : anIndex;
> > >  buffer : aBuffer;
>
> > This is backwards to me:
>
> >   anIndex : Index;
> >   aBuffer : Buffer;
>
> > E.g. the value is a specific instance vs the type is general. The names should
> > reflect that.

IIRC the rationale for "index : anIndex" is that it sounds like
English "index is an Index". Natural language syntax is a bitch!

Jeffrey R. Carter

unread,
Aug 7, 2008, 3:25:55 PM8/7/08
to
Georg Bauhaus wrote:
>
> The identity can be a bit of a formal identity.
> For example, a subprogram parameter name designates a
> specific object during each invocation. But there are
> many invocations. Each gets a different specific node.
> In this case, a convention is to use the prefix
> "The_" to indicate identity:
>
> procedure Foo(The_Node: ....);

Prefixes are a very bad idea. Psychologically, the first few characters of an
identifier are the most important in recognizing it. When multiple identifiers
start with the same prefix, recognition is made more difficult. The ease of
understanding is reduced compared to the same code without common prefixes.

--
Jeff Carter
"To Err is human, to really screw up, you need C++!"
Stéphane Richard
63

Adam Beneschan

unread,
Aug 7, 2008, 3:27:28 PM8/7/08
to
On Aug 7, 10:01 am, Ray Blaak <rAYbl...@STRIPCAPStelus.net> wrote:

> Before I get blasted about the evils of case insensitivity, I should point out
> that Java is a unicode language, allows unicode in its identifiers, and case
> folding is not sensical in the general case for unicode characters. With Ada
> being essentially an ASCII language, the case folding debate has merit.

First of all, Java (like C and Unix) is case-sensitive, not case-
insensitive. Ada is case-insensitive. You have the two backwards.

Second, Ada (starting with Ada 2005) does allow ISO 10646 (Unicode)
characters in its identifiers, and it defines how it handles its case
insensitivity for identifiers, which I think involves the "Uppercase
Mapping" defined by ISO 10646:2003. So case folding does make sense
for programming languages that allow Unicode characters in
identifiers, including Ada.

-- Adam

Jeffrey R. Carter

unread,
Aug 7, 2008, 3:37:28 PM8/7/08
to
amado...@gmail.com wrote:
> IIRC the rationale for "index : anIndex" is that it sounds like
> English "index is an Index". Natural language syntax is a bitch!

"Index is an index" is at best a tautology and at worst meaningless; in other
words, this approach adds no value. Yet another mindless rule to avoid the
effort of thinking up good names.

"Index" is a poor variable name. What is it the index of?

First_Comma : Index_Value;
Start_Position : Index_Value;

and so on. Good names add information.

Ray Blaak

unread,
Aug 7, 2008, 6:15:07 PM8/7/08
to
Adam Beneschan <ad...@irvine.com> writes:
> On Aug 7, 10:01 am, Ray Blaak <rAYbl...@STRIPCAPStelus.net> wrote:
>
> > Before I get blasted about the evils of case insensitivity, I should point out
> > that Java is a unicode language, allows unicode in its identifiers, and case
> > folding is not sensical in the general case for unicode characters. With Ada
> > being essentially an ASCII language, the case folding debate has merit.
>
> First of all, Java (like C and Unix) is case-sensitive, not case-
> insensitive. Ada is case-insensitive. You have the two backwards.

Ack! Of course. Thanks for the correction.

>
> Second, Ada (starting with Ada 2005) does allow ISO 10646 (Unicode)
> characters in its identifiers, and it defines how it handles its case
> insensitivity for identifiers, which I think involves the "Uppercase
> Mapping" defined by ISO 10646:2003. So case folding does make sense
> for programming languages that allow Unicode characters in
> identifiers, including Ada.

I guess they were forced to deal with it somehow. It's a problem I would
rather just avoid, myself.

Ray Blaak

unread,
Aug 7, 2008, 6:17:28 PM8/7/08
to
Ray Blaak <rAYb...@STRIPCAPStelus.net> writes:
> At the risk of offense, being an Ada group and all, I must point out that
> Java's case insensitivity allows this kind of thing:
>
> Node node;

Java's case SENSITIVITY, of course.

Steve

unread,
Aug 8, 2008, 9:46:19 AM8/8/08
to
"Jeffrey R. Carter" <spam.jrc...@spam.acm.org> wrote in message
news:Y9Imk.287972$yE1.85979@attbi_s21...

> amado...@gmail.com wrote:
>> IIRC the rationale for "index : anIndex" is that it sounds like
>> English "index is an Index". Natural language syntax is a bitch!
>
> "Index is an index" is at best a tautology and at worst meaningless; in
> other words, this approach adds no value. Yet another mindless rule to
> avoid the effort of thinking up good names.
>
> "Index" is a poor variable name. What is it the index of?
>
> First_Comma : Index_Value;
> Start_Position : Index_Value;
>
> and so on. Good names add information.

Funny, with my simple example of anIndex you comment that anIndex is
meaningless and go on to use Index_Value as being more informative. Your
example is to simple and worthless as well. All variables contain values.

Perhaps a better example is more like:

lengthIndex : aLengthTableIndex;

is more useful.

And yes the way I read it is in the natural language way:

lengthIndex is a length length table index.

I've seen code that uses the a prefix on variable names. After getting used
to the opposite convention it makes it hard to read.

Personally I prefer the _Type and _Acc_Type suffixes.

One other thing to note: Once I got used to reading and writing code using
these conventions, I found:
1) It makes reading code that follows these conventions a lot easier
2) It makes reading code that does not follow these conventions harder
(you get used not having to infer based on context).

Regards,
Steve

Ray Blaak

unread,
Aug 8, 2008, 12:40:11 PM8/8/08
to
"Steve" <nospam_...@comcast.net> writes:
> One other thing to note: Once I got used to reading and writing code using
> these conventions, I found:
> 1) It makes reading code that follows these conventions a lot easier
> 2) It makes reading code that does not follow these conventions harder
> (you get used not having to infer based on context).

This is the problem with getting attached to any particular convention.

If you review a lot of other people's code, you tend to learn how to look past
a lot of these conventions.

There also tends to be a standard naming convention for each language, and
that in fact is the best convention to use, even if you don't completely agree
with it. The reason is that this maximizes how your code can be reviewed and
maintained by others.

Jeffrey R. Carter

unread,
Aug 8, 2008, 4:27:41 PM8/8/08
to
Steve wrote:
>
> Funny, with my simple example of anIndex you comment that anIndex is
> meaningless and go on to use Index_Value as being more informative. Your
> example is to simple and worthless as well. All variables contain values.

I'm glad to hear that you think "Index is an index" is more meaningful than
"Start position is an index value".

--
Jeff Carter
"We call your door-opening request a silly thing."
Monty Python & the Holy Grail
17

Simon Wright

unread,
Aug 12, 2008, 10:00:59 AM8/12/08
to
amado...@gmail.com writes:

> And in sum, whatever the form, it's good to see that more Adaists are
> suffixists :-)

Those of us who are militantly against _T were perhaps on holiday ...

I believe that type names for units of measure should be plural, as in
common (English) usage:

type Metres is digits 6;

and that enumerations should be singular:

type Hostility is (Unknown, Friendly, Neutral, Hostile);

and see nothing wrong with short names for local variables or procedure
parameters:

H : Hostility;
I : Index;

though I admit it's not so clear for record components, which are much
more widely visible.

A lot of the reason for lack of clarity is that people don't spend
enough time thinking of the right names for things. The _T pattern can
let them off the hook too easily.

I do like _P for pointer types (and _G for generics), though!

Martin

unread,
Aug 19, 2008, 2:05:58 PM8/19/08
to
On Aug 7, 6:04 pm, Ray Blaak <rAYbl...@STRIPCAPStelus.net> wrote:

> Colin Paul Gloster <Colin_Paul_Glos...@ACM.org> writes:
>
> >  index : anIndex;
> >  buffer : aBuffer;
>
> This is backwards to me:
>
>   anIndex : Index;
>   aBuffer : Buffer;
>
> E.g. the value is a specific instance vs the type is general. The names should
> reflect that.
>
> --
> Cheers,                                        The Rhythm is around me,
>                                                The Rhythm has control.
> Ray Blaak                                      The Rhythm is inside me,
> rAYbl...@STRIPCAPStelus.net                    The Rhythm has my soul.

Ah, but "a" (or "an_") are 'indefinite articles' in English (which
this is obviously trying to replicate), i.e. they don't specify any
particular instance. A variable does specify a particulary instance,
so using "a_"/"an_" for them is wrong. "better names" are what are
always called for :-)

The_Buffer : A_Buffer;
The_Index : An_Index;

or

My_Buffer : A_Buffer;

or

User_Input_Buffer : A_Buffer;

etc

I've used (and mandated) the "A_"/"An_" prefixes on a few projects and
it does work quite well and read fine.

I'll put my hand up and admit I _hate_ the noise of "_Type" - it
really ought to be clear and unambiguous from language rules but
isn't. :-(

Cheers
-- Martin

Ray Blaak

unread,
Aug 19, 2008, 7:04:19 PM8/19/08
to
Martin <martin...@btopenworld.com> writes:
> Ah, but "a" (or "an_") are 'indefinite articles' in English (which
> this is obviously trying to replicate), i.e. they don't specify any
> particular instance. A variable does specify a particulary instance,
> so using "a_"/"an_" for them is wrong. "better names" are what are
> always called for :-)
>
> The_Buffer : A_Buffer;

A type is not an indefinite instance either, or any instance at all. A type is
a contract specifying behaviour and storage.

My suspicion is that this is motivated so that it reads better in English,
e.g. "the buffer is a buffer".

Unfortunately, this is not the semantics of the programming language. The
semantics are:

"The_Buffer" is now in scope, and its type is "Buffer".

This is more succinctly expressed as:

The_Buffer : Buffer

As programmers we are quite used to understanding code. We are required to
keep things readable *and* accurate.

> I've used (and mandated) the "A_"/"An_" prefixes on a few projects and
> it does work quite well and read fine.

Well, there you go. Use it as you like if it works for you, but I can't stand
it.

--
Cheers, The Rhythm is around me,
The Rhythm has control.
Ray Blaak The Rhythm is inside me,

rAYb...@STRIPCAPStelus.net The Rhythm has my soul.

Gary Scott

unread,
Aug 19, 2008, 8:13:50 PM8/19/08
to
Ray Blaak wrote:

> Martin <martin...@btopenworld.com> writes:
>
>>Ah, but "a" (or "an_") are 'indefinite articles' in English (which
>>this is obviously trying to replicate), i.e. they don't specify any
>>particular instance. A variable does specify a particulary instance,
>>so using "a_"/"an_" for them is wrong. "better names" are what are
>>always called for :-)
>>
>>The_Buffer : A_Buffer;
>
>
> A type is not an indefinite instance either, or any instance at all. A type is
> a contract specifying behaviour and storage.
>
> My suspicion is that this is motivated so that it reads better in English,
> e.g. "the buffer is a buffer".
>
> Unfortunately, this is not the semantics of the programming language. The
> semantics are:
>
> "The_Buffer" is now in scope, and its type is "Buffer".
>
> This is more succinctly expressed as:
>
> The_Buffer : Buffer
>
> As programmers we are quite used to understanding code. We are required to
> keep things readable *and* accurate.
>
>
>>I've used (and mandated) the "A_"/"An_" prefixes on a few projects and
>>it does work quite well and read fine.
>
>
> Well, there you go. Use it as you like if it works for you, but I can't stand
> it.
>

It is very common to use naming conventions to lessen the ambituity,
especially when it is likely to be interpreted by users of other
programming languages. Ada isn't always as readable (conversational) as
some other languages.

--

Gary Scott
mailto:garylscott@sbcglobal dot net

Fortran Library: http://www.fortranlib.com

Support the Original G95 Project: http://www.g95.org
-OR-
Support the GNU GFortran Project: http://gcc.gnu.org/fortran/index.html

If you want to do the impossible, don't hire an expert because he knows
it can't be done.

-- Henry Ford

Steve

unread,
Aug 19, 2008, 10:01:45 PM8/19/08
to
>"Martin" <martin...@btopenworld.com> wrote in message
>news:efded36d-c0f1-45f9-b1ac->f3575f...@w7g2000hsa.googlegroups.com...
[snip]

>I've used (and mandated) the "A_"/"An_" prefixes on a few projects and
>it does work quite well and read fine.
>
>I'll put my hand up and admit I _hate_ the noise of "_Type" - it
>really ought to be clear and unambiguous from language rules but
>isn't. :-(

Actually I think it is clear from the language rules, but...

When reading source code it is often important to be able to scan through
code quickly and comprehend the meaning. Coding conventions can make it
quicker to recognize things in without reading the text.

For example indenting code uniformly makes it easier to follow. While the
format of the code doesn't change its meaning, it can make it considerably
easier to read.

Regards,
Steve


>Cheers
>-- Martin


Georg Bauhaus

unread,
Aug 20, 2008, 3:42:17 AM8/20/08
to
Ray Blaak wrote:

> A type is a contract specifying behaviour and storage.

In the context of Ada types, this use of the word "contract" is
potentially eroding the very notion of contract. A type is not
specific enough to be the same as a proper full contract:


Behavior includes time. Most types don't say anything about time.
Behavior includes order. Most types don't say anything about order
of operations. The client party can choose any order of primitive
operations they wish. They can expect the operations to have finished
whenever these are done. No contractual specifics.

Contracts say, "Provided earlier behavior X... ",
"Provided property P of A ... ". Most Ada types do not and cannot
currently have a contractual part of this sort. There are no
premises right now, other than subtype constraints (recursively).

The client party to a type-contract is typically *not* granted access
to any piece of storage. Client parties only see the
public view of a type. You could say that privacy is part of the
contract. Sure. This is what I mean by eroding the notion of "contract".

(It is typically not necessary to set up a contract between two parties
when all that it specifies is,
"Client will not tear castle's walls down."
That's understood.)

A contract for object of a type typically *exludes* aspects of
storage. (Other than saying, this operation requires O(2*n) words
of computer storage. Said in comments...)

A contract is specific about expectations. "This function returns
a String" is unspecific at the level of "contract". The client's
expectation in the sense of contract is, "What kind of String will
I get back?"


I think it might be advantageous to let "contract" mean the
essentials that make contract *different* from plain old
Ada type.


--
Georg Bauhaus
Y A Time Drain http://www.9toX.d

Martin

unread,
Aug 20, 2008, 4:52:07 AM8/20/08
to
Ray Blaak wrote:
> Martin <martin...@btopenworld.com> writes:
[snip]

> A type is not an indefinite instance either, or any instance at all. A type is
> a contract specifying behaviour and storage.

But that's pretty much defines an indefinite article...it isn't an
instance.


> My suspicion is that this is motivated so that it reads better in English,
> e.g. "the buffer is a buffer".
>
> Unfortunately, this is not the semantics of the programming language. The
> semantics are:
>
> "The_Buffer" is now in scope, and its type is "Buffer".
>
> This is more succinctly expressed as:
>
> The_Buffer : Buffer
>
> As programmers we are quite used to understanding code. We are required to
> keep things readable *and* accurate.

I'm not sure how one is more or less accurate than the other - you
could equally have written
"The_Buffer" is now in scope, and its type is "A_Buffer".

The important bit (semantically) is the bit about 'scope' that we both
had to hand write and which had nothing to do with the name of either
the object or the type...


> > I've used (and mandated) the "A_"/"An_" prefixes on a few projects and
> > it does work quite well and read fine.
>
> Well, there you go. Use it as you like if it works for you, but I can't stand
> it.

Yes, it is mostly a "taste" thing...but if you do wish to 'mimic'
English, then types not objects are definitely indefinite! ;-)


> --
> Cheers, The Rhythm is around me,
> The Rhythm has control.
> Ray Blaak The Rhythm is inside me,
> rAYb...@STRIPCAPStelus.net The Rhythm has my soul.

Gabriel is good...only with 1 'o' :-)

Stephen Leake

unread,
Aug 20, 2008, 7:53:28 AM8/20/08
to
Martin <martin...@btopenworld.com> writes:

> I've used (and mandated) the "A_"/"An_" prefixes on a few projects and
> it does work quite well and read fine.
>
> I'll put my hand up and admit I _hate_ the noise of "_Type" - it
> really ought to be clear and unambiguous from language rules but
> isn't. :-(

But you find the noise of "A_" more acceptable? that seems odd. I
prefer "_Type"; it doesn't try to introduce any more meaning than is
already there from the language rules.

At least we agree that some noise in the type name is necessary, due
to a wart in the language.

I use "wart" to mean "ugliness, but not easy to fix, so we can't call
it a bug".

--
-- Stephe

Stephen Leake

unread,
Aug 20, 2008, 7:59:07 AM8/20/08
to
"Steve" <nospam_...@comcast.net> writes:

>>"Martin" <martin...@btopenworld.com> wrote in message
>>news:efded36d-c0f1-45f9-b1ac->f3575f...@w7g2000hsa.googlegroups.com...
> [snip]
>>I've used (and mandated) the "A_"/"An_" prefixes on a few projects and
>>it does work quite well and read fine.
>>
>>I'll put my hand up and admit I _hate_ the noise of "_Type" - it
>>really ought to be clear and unambiguous from language rules but
>>isn't. :-(
>
> Actually I think it is clear from the language rules, but...

Huh? The problem is that the language rules forbid this:

Buffer : Buffer;

That is what we would _like_ the language to allow.

> When reading source code it is often important to be able to scan through
> code quickly and comprehend the meaning. Coding conventions can make it
> quicker to recognize things in without reading the text.

So can clear language rules! If we assume that the reader _fully_
understands the language, extra noise like "_Type" or "A_" just get in
the way.

Fortunately, the human mind/brain is good at filtering out such noise,
as long as it is present consistently.

If we try to right Ada code so someone who understands only some
C-like language can read it, then coding conventions might help. I
avoid doing that; one of my goals is to stamp out C coding :).

> For example indenting code uniformly makes it easier to follow.

That's true, independent of language rules.

--
-- Stephe

Martin

unread,
Aug 20, 2008, 8:12:46 AM8/20/08
to
On Aug 20, 12:53 pm, Stephen Leake <stephen_le...@stephe-leake.org>
wrote:

Yes - it's 3 character less typing! :-)

But yes, it's still "ugly" and it would be nice to be able to not have
to do anything like this.

Cheers
-- Martin

Adam Beneschan

unread,
Aug 20, 2008, 10:25:12 AM8/20/08
to
On Aug 20, 4:59 am, Stephen Leake <stephen_le...@stephe-leake.org>
wrote:
> "Steve" <nospam_steve...@comcast.net> writes:
> >>"Martin" <martin.do...@btopenworld.com> wrote in message

>
> >>I've used (and mandated) the "A_"/"An_" prefixes on a few projects and
> >>it does work quite well and read fine.
>
> >>I'll put my hand up and admit I _hate_ the noise of "_Type" - it
> >>really ought to be clear and unambiguous from language rules but
> >>isn't. :-(
>
> > Actually I think it is clear from the language rules, but...
>
> Huh? The problem is that the language rules forbid this:
>
> Buffer : Buffer;
>
> That is what we would _like_ the language to allow.

Yeah, earlier on in this thread I was thinking about whether it would
have been possible for Ada to have separate namespaces for types and
other non-type entities without ambiguities. Attributes make this
impossible. Offhand, I'm not sure whether context is always
sufficient to distinguish types from non-types, other than with
attributes. Not that any of this is particularly relevant, except to
those who might be thinking of designing new languages....

-- Adam

Dmitry A. Kazakov

unread,
Aug 20, 2008, 11:38:04 AM8/20/08
to
On Wed, 20 Aug 2008 07:25:12 -0700 (PDT), Adam Beneschan wrote:

> Yeah, earlier on in this thread I was thinking about whether it would
> have been possible for Ada to have separate namespaces for types and
> other non-type entities without ambiguities. Attributes make this
> impossible.

Nope. In all cases the type and variable names can be overloaded. Any
difference between them is not lexical.

> Offhand, I'm not sure whether context is always
> sufficient to distinguish types from non-types, other than with
> attributes.

That is not required by Ada design, which permits hiding and clashes of
names.

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

Gary Scott

unread,
Aug 20, 2008, 11:46:03 AM8/20/08
to
Stephen Leake wrote:
> "Steve" <nospam_...@comcast.net> writes:
>
>
>>>"Martin" <martin...@btopenworld.com> wrote in message
>>>news:efded36d-c0f1-45f9-b1ac->f3575f...@w7g2000hsa.googlegroups.com...
>>
>>[snip]
>>
>>>I've used (and mandated) the "A_"/"An_" prefixes on a few projects and
>>>it does work quite well and read fine.
>>>
>>>I'll put my hand up and admit I _hate_ the noise of "_Type" - it
>>>really ought to be clear and unambiguous from language rules but
>>>isn't. :-(
>>
>>Actually I think it is clear from the language rules, but...
>
>
> Huh? The problem is that the language rules forbid this:
>
> Buffer : Buffer;
>
> That is what we would _like_ the language to allow.

what? that looks completely ambiguous in terms of readability. you
must know some arcane rule to interpret it.

>
>
>>When reading source code it is often important to be able to scan through
>>code quickly and comprehend the meaning. Coding conventions can make it
>>quicker to recognize things in without reading the text.
>
>
> So can clear language rules! If we assume that the reader _fully_
> understands the language, extra noise like "_Type" or "A_" just get in
> the way.
>
> Fortunately, the human mind/brain is good at filtering out such noise,
> as long as it is present consistently.
>
> If we try to right Ada code so someone who understands only some
> C-like language can read it, then coding conventions might help. I
> avoid doing that; one of my goals is to stamp out C coding :).
>
>
>>For example indenting code uniformly makes it easier to follow.
>
>
> That's true, independent of language rules.
>


--

Gary Scott

Ray Blaak

unread,
Aug 20, 2008, 12:19:16 PM8/20/08
to
Georg Bauhaus <see.re...@maps.futureapps.de> writes:

> Ray Blaak wrote:
>
> > A type is a contract specifying behaviour and storage.
>
> In the context of Ada types, this use of the word "contract" is
> potentially eroding the very notion of contract. A type is not
> specific enough to be the same as a proper full contract:

I guess I meant that in the natural English sense. A type is a contract in
that it specifies what it specifies.

If that fails to specify time, order, exceptions, that is a separate issue.

My point is not to debate what a contract is as such, but to emphasize that a
type is not an indefinite instance, but a way of specifying (some) properties
of instances.

Simon Wright

unread,
Aug 20, 2008, 3:37:31 PM8/20/08
to
Stephen Leake <stephe...@stephe-leake.org> writes:

> At least we agree that some noise in the type name is necessary, due
> to a wart in the language.

_Sometimes_ necessary, often because of a failure of imagination on the
part of the developers!

Adam Beneschan

unread,
Aug 20, 2008, 4:37:03 PM8/20/08
to
On Aug 20, 8:38 am, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:

> On Wed, 20 Aug 2008 07:25:12 -0700 (PDT), Adam Beneschan wrote:
> > Yeah, earlier on in this thread I was thinking about whether it would
> > have been possible for Ada to have separate namespaces for types and
> > other non-type entities without ambiguities. Attributes make this
> > impossible.
>
> Nope. In all cases the type and variable names can be overloaded. Any
> difference between them is not lexical.

Apparently I didn't make myself clear, since we seem to be talking
about two totally different things. Either that, or I just don't
understand what you're saying.

Let me try to make myself clearer: If there were a rule change in Ada
so that types (or subtypes) could have the same identifiers as other
entities in the same scope, in many or most cases the compiler could
unambiguously determine from context whether the identifier refers to
the type:

XYZ : Some_Type;
type XYZ is array (1..10) of Some_Other_Type;
An_Object : XYZ;

In this last line, it's clear that only the type declaration could be
meant by XYZ. But in attribute cases, it can be ambiguous: XYZ'First,
XYZ'Last, XYZ'Size, probably some others. So that aspect of the
language would need a new design. I'm not sure whether there are
other cases, besides attributes, where the identifier would be
ambiguous.

-- Adam


Peter C. Chapin

unread,
Aug 20, 2008, 9:46:48 PM8/20/08
to
Adam Beneschan wrote:

> XYZ : Some_Type;
> type XYZ is array (1..10) of Some_Other_Type;
> An_Object : XYZ;
>
> In this last line, it's clear that only the type declaration could be
> meant by XYZ.

I'm not sure allowing such a thing, even if were possible, would be a
good idea. Types and instances are conceptually quite different and
allowing them to reuse the same name (in the same scope) sounds
confusing. After all, a set of integers is different than any particular
integer and I don't want to loose sight of that when I'm looking at my code.

Peter

Stephen Leake

unread,
Aug 21, 2008, 5:44:09 AM8/21/08
to
Simon Wright <simon.j...@mac.com> writes:

There is enough work for my mind to do; why should I waste energy on
this issue when there is an extremely simple and perfectly reasonable
solution?

--
-- Stephe

Dmitry A. Kazakov

unread,
Aug 21, 2008, 5:44:21 AM8/21/08
to

My point is that this does not differ from the case when XYZ are two
variables visible from two different packages:

package A is
XYZ : Some_Type;
end A;

package B is
XYZ : Some_Type;
end B;

use A, B and XYZ'First will be ambiguous. It is not a lexical problem.
S'First is just an expression it might be ambiguous. So what?

The real problem is that the ambiguity might be impossible to resolve. But
this isn't new. There already exist cases when names get hidden forever.

So long types are not first-class citizens in Ada, we could have a
different namespace for them. Not that I would advocate for that!

Stephen Leake

unread,
Aug 21, 2008, 5:47:32 AM8/21/08
to

The set is after the colon, the particular is before it. Most of the
time it is clear from context.

Except, as Adam points out, when using attributes.

It would save all these hours of arguing over _Type vs A_ vs "use more
imagination" :).

--
-- Stephe

Stephen Leake

unread,
Aug 21, 2008, 5:48:55 AM8/21/08
to
Gary Scott <garyl...@sbcglobal.net> writes:

> Stephen Leake wrote:
>> Huh? The problem is that the language rules forbid this:
>>
>> Buffer : Buffer;
>>
>> That is what we would _like_ the language to allow.
>
> what? that looks completely ambiguous in terms of readability. you
> must know some arcane rule to interpret it.

The object is before the colon, the type is after it. Nothing "arcane"
about that. It's just Ada. Different from C, of course.
--
-- Stephe

Dmitry A. Kazakov

unread,
Aug 21, 2008, 5:49:56 AM8/21/08
to
On Wed, 20 Aug 2008 21:46:48 -0400, Peter C. Chapin wrote:

> I'm not sure allowing such a thing, even if were possible, would be a
> good idea. Types and instances are conceptually quite different and
> allowing them to reuse the same name (in the same scope) sounds
> confusing.

Hmm, exactly because they are so different, it is safe to share names
between them. (I am not arguing in favor of such a step, though)

amado...@gmail.com

unread,
Aug 21, 2008, 9:53:38 AM8/21/08
to
> Buffer : Buffer;

This is horrible! Total lack of intuitiveness. You must have imprint
in your brain a totally arbitrary rule. Very hard--maybe only for us
dislexics. Add the little suffix and voila, all is clear in all
languages :-)

Buffer : Buffer_T; -- Ada, Pascal...

Buffer_T Buffer; -- C, C++...

Gary Scott

unread,
Aug 21, 2008, 11:30:53 AM8/21/08
to
Fortram

type(Buffer_T) :: Buffer

Randy Brukardt

unread,
Aug 22, 2008, 12:12:01 AM8/22/08
to
"Adam Beneschan" <ad...@irvine.com> wrote in message
news:2259e1a3-e04c-4662...@x16g2000prn.googlegroups.com...
...

> Let me try to make myself clearer: If there were a rule change in Ada
> so that types (or subtypes) could have the same identifiers as other
> entities in the same scope, in many or most cases the compiler could
> unambiguously determine from context whether the identifier refers to
> the type:

Type conversions and array indexing also would be ambiguous:

Some_Array : Some_Array;

... Some_Array (<expr>) ...

I think that would be much worse than attributes (they're used a lot more,
especially array indexing).

Of course, a language supporting that could have used square brackets for
indexing (like Pascal), and get rid of that problem. But it won't work in
Ada.

Randy.


Randy Brukardt

unread,
Aug 22, 2008, 12:12:01 AM8/22/08
to
"Adam Beneschan" <ad...@irvine.com> wrote in message
news:2259e1a3-e04c-4662...@x16g2000prn.googlegroups.com...
...
> Let me try to make myself clearer: If there were a rule change in Ada
> so that types (or subtypes) could have the same identifiers as other
> entities in the same scope, in many or most cases the compiler could
> unambiguously determine from context whether the identifier refers to
> the type:

Type conversions and array indexing also would be ambiguous:

0 new messages