Ada Style Guide/Readability

From Wikibooks, open books for an open world
Jump to navigation Jump to search

Source Code Presentation · Program Structure

Introduction[edit | edit source]

This chapter recommends ways of using Ada features to make reading and understanding code easier. There are many myths about comments and readability. The responsibility for true readability rests more with naming and code structure than with comments. Having as many comment lines as code lines does not imply readability; it more likely indicates the writer does not understand what is important to communicate.

Spelling[edit | edit source]

Spelling conventions in source code include rules for capitalization and use of underscores, numbers, and abbreviations. If you follow these conventions consistently, the resulting code is clearer and more readable.

Use of Underscores[edit | edit source]

guideline[edit | edit source]

  • Use underscores to separate words in a compound name.

example[edit | edit source]

Miles_Per_Hour
Entry_Value

rationale[edit | edit source]

When an identifier consists of more than one word, it is much easier to read if the words are separated by underscores. Indeed, there is precedent in English in which compound words are separated by a hyphen or a space. In addition to promoting readability of the code, if underscores are used in names, a code formatter has more control over altering capitalization. See Guideline 3.1.3.

Numbers[edit | edit source]

guideline[edit | edit source]

  • Represent numbers in a consistent fashion.
  • Represent literals in a radix appropriate to the problem.
  • Use underscores to separate digits the same way commas or periods (or spaces for nondecimal bases) would be used in normal text.
  • When using scientific notation, make the E consistently either uppercase or lowercase.
  • In an alternate base, represent the alphabetic characters in either all uppercase or all lowercase.

instantiation[edit | edit source]

  • Decimal and octal numbers are grouped by threes beginning on the left side of the radix point and by fives beginning on the right side of the radix point.
  • The E is always capitalized in scientific notation.
  • Use uppercase for the alphabetic characters representing digits in bases above 10.
  • Hexadecimal numbers are grouped by fours beginning on either side of the radix point.

example[edit | edit source]

type Maximum_Samples     is range          1 ..  1_000_000;
type Legal_Hex_Address   is range   16#0000# ..   16#FFFF#;
type Legal_Octal_Address is range 8#000_000# .. 8#777_777#;

Avogadro_Number : constant := 6.02216_9E+23;

To represent the number 1/3 as a constant, use:

One_Third : constant := 1.0 / 3.0;

Avoid this use:

One_Third_As_Decimal_Approximation : constant := 0.33333_33333_3333;

or:

One_Third_Base_3 : constant := 3#0.1#;

rationale[edit | edit source]

Consistent use of uppercase or lowercase aids scanning for numbers. Underscores serve to group portions of numbers into familiar patterns. Consistency with common use in everyday contexts is a large part of readability.

notes[edit | edit source]

If a rational fraction is represented in a base in which it has a terminating rather than a repeating representation, as 3#0.1# does in the example above, it may have increased accuracy upon conversion to the machine base. (This is wrong for named numbers as in this example - they must be calculated exactly.)

Capitalization[edit | edit source]

guideline[edit | edit source]

  • Make reserved words and other elements of the program visually distinct from each other.

instantiation[edit | edit source]

  • Use lowercase for all reserved words (when used as reserved words).
  • Use mixed case for all other identifiers, a capital letter beginning every word separated by underscores.
  • Use uppercase for abbreviations and acronyms (see automation notes).

example[edit | edit source]

...

type Second_Of_Day      is range 0 .. 86_400;
type Noon_Relative_Time is (Before_Noon, After_Noon, High_Noon);

subtype Morning   is Second_Of_Day range 0 .. 86_400 / 2 - 1;
subtype Afternoon is Second_Of_Day range Morning'Last + 2 .. 86_400;

...

Current_Time := Second_Of_Day(Calendar.Seconds(Calendar.Clock));
if Current_Time in Morning then
   Time_Of_Day := Before_Noon;
elsif Current_Time in Afternoon then
   Time_Of_Day := After_Noon;
else
   Time_Of_Day := High_Noon;
end if;

case Time_Of_Day is
   when Before_Noon =>   Get_Ready_For_Lunch;
   when High_Noon   =>   Eat_Lunch;
   when After_Noon  =>   Get_To_Work;
end case;

...

rationale[edit | edit source]

Visually distinguishing reserved words allows you to focus on program structure alone, if desired, and also aids scanning for particular identifiers.

The instantiation chosen here is meant to be more readable for the experienced Ada programmer, who does not need reserved words to leap off the page. Beginners to any language often find that reserved words should be emphasized to help them find the control structures more easily. Because of this, instructors in the classroom and books introducing the Ada language may want to consider an alternative instantiation. The Ada Reference Manual (1995) chose bold lowercase for all reserved words.

automation notes[edit | edit source]

Ada names are not case sensitive. Therefore, the names max_limit, MAX_LIMIT, and Max_Limit denote the same object or entity. A good code formatter should be able to automatically convert from one style to another as long as the words are delimited by underscores.

As recommended in Guideline 3.1.4, abbreviations should be project-wide. An automated tool should allow a project to specify those abbreviations and format them accordingly.

Abbreviations[edit | edit source]

guideline[edit | edit source]

  • Do not use an abbreviation of a long word as an identifier where a shorter synonym exists.
  • Use a consistent abbreviation strategy.
  • Do not use ambiguous abbreviations.
  • To justify its use, an abbreviation must save many characters over the full word.
  • Use abbreviations that are well-accepted in the application domain.
  • Maintain a list of accepted abbreviations, and use only abbreviations on that list.

example[edit | edit source]

Use:

Time_Of_Receipt

rather than:

Recd_Time or R_Time

But in an application that commonly deals with message formats that meet military standards, DOD_STD_MSG_FMT is an acceptable abbreviation for:

Department_Of_Defense_Standard_Message_Format.

rationale[edit | edit source]

Many abbreviations are ambiguous or unintelligible unless taken in context. As an example, Temp could indicate either temporary or temperature. For this reason, you should choose abbreviations carefully when you use them. The rationale in Guideline 8.1.2 provides a more thorough discussion of how context should influence the use of abbreviations.

Because very long variable names can obscure the structure of the program, especially in deeply nested (indented) control structures, it is a good idea to try to keep identifiers short and meaningful. Use short unabbreviated names whenever possible. If there is no short word that will serve as an identifier, then a well-known unambiguous abbreviation is the next best choice, especially if it comes from a list of standard abbreviations used throughout the project.

You can establish an abbreviated format for a fully qualified name using the renames clause. This capability is useful when a very long, fully qualified name would otherwise occur many times in a localized section of code (see Guideline 5.7.2).

A list of accepted abbreviations for a project provides a standard context for using each abbreviation.

Naming Conventions[edit | edit source]

Choose names that clarify the object's or entity's intended use. Ada allows identifiers to be any length as long as the identifier fits on a line with all characters being significant (including underscores). Identifiers are the names used for variables, constants, program units, and other entities within a program.

Names[edit | edit source]

guideline[edit | edit source]

  • Choose names that are as self-documenting as possible.
  • Use a short synonym instead of an abbreviation (see Guideline 3.1.4).
  • Use names given by the application, but do not use obscure jargon.
  • Avoid using the same name to declare different kinds of identifiers.

example[edit | edit source]

In a tree-walker, using the name Left instead of Left_Branch is sufficient to convey the full meaning given the context. However, use Time_Of_Day instead of TOD.

Mathematical formulas are often given using single-letter names for variables. Continue this convention for mathematical equations where they would recall the formula, for example:

   A*(X**2) + B*X + C.

With the use of child packages, a poor choice of package, subunit, and identifier names can lead to a visibility clash with subunits. See the Rationale (1995, §8.1) for a sample of the resulting, rather obscure code.

rationale[edit | edit source]

A program that follows these guidelines can be more easily comprehended. Self-documenting names require fewer explanatory comments. Empirical studies have shown that you can further improve comprehension if your variable names are not excessively long (Schneiderman 1986, 7). The context and application can help greatly. The unit of measure for numeric entities can be a source of subtype names.

You should try not to use the same name as an identifier for different declarations, such as an object and a child package. Overusing an identifier in seemingly different name spaces can, in fact, lead to visibility clashes if the enclosing program units are intended to work together.

notes[edit | edit source]

See Guideline 8.1.2 for a discussion on how to use the application domain as a guideline for selecting abbreviations.

Subtype Names[edit | edit source]

guideline[edit | edit source]

  • Use singular, general nouns as subtype identifiers.
  • Choose identifiers that describe one of the subtype's values.
  • Consider using suffixes for subtype identifiers that define visible access types, visible subranges, or visible array types.
  • For private types, do not use identifier constructions (e.g., suffixes) that are unique to subtype identifiers.
  • Do not use the subtype names from predefined packages.

example[edit | edit source]

type Day is
   (Monday,    Tuesday,   Wednesday, Thursday,  Friday,
    Saturday,  Sunday);

type Day_Of_Month    is range      0 ..    31;
type Month_Number    is range      1 ..    12;
type Historical_Year is range -6_000 .. 2_500;

type Date is
   record
      Day   : Day_Of_Month;
      Month : Month_Number;
      Year  : Historical_Year;
   end record;

In particular, Day should be used in preference to Days or Day_Type.

The identifier Historical_Year might appear to be specific, but it is actually general, with the adjective historical describing the range constraint:

------------------------------------------------------------------------
procedure Disk_Driver is
 
   -- In this procedure, a number of important disk parameters are
   -- linked.
   Number_Of_Sectors  : constant :=     4;
   Number_Of_Tracks   : constant :=   200;
   Number_Of_Surfaces : constant :=    18;
   Sector_Capacity    : constant := 4_096;

   Track_Capacity   : constant := Number_Of_Sectors  * Sector_Capacity;
   Surface_Capacity : constant := Number_Of_Tracks   * Track_Capacity;
   Disk_Capacity    : constant := Number_Of_Surfaces * Surface_Capacity;

   type Sector_Range  is range 1 .. Number_Of_Sectors;
   type Track_Range   is range 1 .. Number_Of_Tracks;
   type Surface_Range is range 1 .. Number_Of_Surfaces;

   type Track_Map   is array (Sector_Range)  of ...;
   type Surface_Map is array (Track_Range)   of Track_Map;
   type Disk_Map    is array (Surface_Range) of Surface_Map;

begin  -- Disk_Driver
   ...
end Disk_Driver;
------------------------------------------------------------------------

The suffixes _Capacity, _Range, and _Map help define the purpose of the above subtypes and avoid the search for synonyms for the sector, track, and surface abstractions. Without the suffixes, you would need three different names per abstraction, one to describe each of the concepts succinctly named in the suffix. This recommendation only applies to certain visible subtypes. Private types, for example, should be given a good name that reflects the abstraction being represented.

rationale[edit | edit source]

When this style and the suggested style for object identifiers are used, program code more closely resembles English (see Guideline 3.2.3). Furthermore, this style is consistent with the names of the language's predefined identifiers. They are not named Integers, Booleans, Integer_Type, or Boolean_Type.

However, using the name of a subtype from the predefined packages is sure to confuse a programmer when that subtype appears somewhere without a package qualification.

notes[edit | edit source]

This style guide tries to be consistent with the Ada Reference Manual (1995) in use of the terms "type" and "subtype" name. In general, a "type" refers to the abstract concept, as in a type declaration, while the "subtype" refers to the name given to that abstract concept in an actual declaration. Thus, what was called a type name in Ada 83 (Ada Reference Manual 1983) is now called a subtype name.

Object Names[edit | edit source]

guideline[edit | edit source]

  • Use predicate clauses or adjectives for Boolean objects.
  • Use singular, specific nouns as object identifiers.
  • Choose identifiers that describe the object's value during execution.
  • Use singular, general nouns as identifiers for record components.

example[edit | edit source]

Non-Boolean objects:

Today           : Day;
Yesterday       : Day;
Retirement_Date : Date;

Boolean objects:

User_Is_Available : Boolean;        -- predicate clause
List_Is_Empty     : Boolean;        -- predicate clause
Empty             : Boolean;        -- adjective
Bright            : Boolean;        -- adjective

rationale[edit | edit source]

Using specific nouns for objects establishes a context for understanding the object's value, which is one of the general values described by the subtype's name (see Guideline 3.2.2). Object declarations become very English-like with this style. For example, the first declaration above is read as "Today is a Day."

General nouns, rather than specific, are used for record components because a record object's name will supply the context for understanding the component. Thus, the following component is understood as "the year of retirement":

Retirement_Date.Year

Following conventions that relate object types and parts of speech makes code read more like text. For example, because of the names chosen, the following code segment needs no comments:

if List_Is_Empty then
   Number_Of_Elements := 0;
else
   Number_Of_Elements := Length_Of_List;
end if;

notes[edit | edit source]

If it is difficult to find a specific noun that describes an object's value during the entire execution of a program, the object is probably serving multiple purposes. Multiple objects should be used in such a case.

Naming of Tagged Types and Associated Packages[edit | edit source]

guideline[edit | edit source]

  • Use a consistent naming convention for tagged types and associated packages.

instantiation[edit | edit source]

Naming conventions spark "religious wars"; therefore, two different instantiations are presented. The first instantiation integrates the use of object-oriented features. Except for two special cases, it applies the same naming conventions to declarations, independent of whether they use an object-oriented feature:

  • Name tagged types no differently than subtype names (see Guideline 3.2.2).
  • Use the prefix Abstract_ for packages that export an abstraction for which you intend to provide multiple implementations (see Guideline 9.2.4).
  • Use the suffix _Mixin for packages that provide units of functionality that can be "mixed in" to core abstractions.

The second instantiation highlights the use of object-oriented features through special names or suffixes:

  • Name class packages after the object they represent, without a suffix (Rosen 1995).
  • Name mixin packages after the facet they represent, appending the suffix _Facet (Rosen 1995).
  • Name the main tagged type Instance (Rosen 1995).
  • Follow the declaration of the specific type with a subtype named Class for the corresponding class-wide type (Rosen 1995).

example[edit | edit source]

The following two-part example from the Rationale (1995, §§4.4.4 and 4.6.2) applies the naming conventions of the first instantiation.

For the first part of this example, assume the type Set_Element was declared elsewhere:

package Abstract_Sets is

   type Set is abstract tagged private;

   -- empty set
   function Empty return Set is abstract;

   -- build set with 1 element
   function Unit (Element: Set_Element) return Set is abstract;

   -- union of two sets
   function Union (Left, Right: Set) return Set is abstract;

   -- intersection of two sets
   function Intersection (Left, Right: Set) return Set is abstract;

   -- remove an element from a set
   procedure Take (From    : in out Set;
                   Element :    out set_Element) is abstract;

   Element_Too_Large : exception;
private
   type Set is abstract tagged null record;
end Abstract_Sets;

with Abstract_Sets;
package Bit_Vector_Sets is   -- one implementation of set abstraction

   type Bit_Set is new Abstract_Sets.Set with private;
   ...
private
   Bit_Set_Size : constant := 64;
   type Bit_Vector is ...
   type Bit_Set is new Abstract_Sets.Set with
      record
         Data : Bit_Vector;
      end record;
end Bit_Vector_Sets;

with Abstract_Sets;
package Sparse_Sets  -- alternate implementation of set abstraction

   type Sparse_Set is new Abstract_Sets.Set with private;
   ...
private
   ...
end Bit_Vector_Sets;

The second part of this example applies the naming convention to mixin packages that support a windowing system:

-- assume you have type Basic_Window is tagged limited private;

generic
   type Some_Window is abstract new Basic_Window with private;
package Label_Mixin is 
   type Window_With_Label is abstract new Some_Window with private;
   ...
private
   ...
end Label_Mixin;

generic
   type Some_Window is abstract new Basic_Window with private;
package Border_Mixin is 
   type Window_With_Label is abstract new Some_Window with private;
   ...
private
   ...
end Border_Mixin;

The following example applies the naming conventions of the second instantiation, as discussed in Rosen (1995):

package Shape is
   subtype Side_Count is range 0 .. 100;
   type Instance (Sides: Side_Count) is tagged private;
   subtype Class is Instance'Class;
   . . .
   -- operations on Shape.Instance
private
   . . .
end Shape;

with Shape; use Shape;
package Line is
   type Instance is new Shape.Instance with private;
   subtype Class is Instance'Class;
   . . .
   -- Overridden or new operations
private
   . . .
end Line;

with Shape; use Shape;
generic
   type Origin is new Shape.Instance;
package With_Color_Facet is
   type Instance is new Origin with private;
   subtype Class is Instance'Class;
   -- operations for colored shapes
private
   . . .
end With_Color_Facet;

with Line; use Line;
with With_Color_Facet;
package Colored_Line is new With_Color_Facet (Line.Instance);

Sample declarations might look like:

Red_Line : Colored_Line.Instance;

procedure Draw (What : Shape.Instance);

The above scheme works whether you use full names or a use clause. As long as you use the same name for all the specific types (i.e., type Instance) and class-wide types, the unqualified names will always hide one another. Thus, the compiler will insist you use full name qualification to resolve the ambiguity introduced by the use clause (Rosen 1995).

rationale[edit | edit source]

You want to use a naming scheme that is consistent and readable and conveys the intent of the abstraction. Ideally, the naming scheme should be uniform in how it handles the different ways in which tagged types are used to create classes. If the naming convention is too rigid, however, you will write code fragments that appear stilted from a readability point of view. By using a similar naming convention for type extension through derivation and through generic mixin (see also Guideline 9.5.1), you achieve readable declarations of objects and procedures.

notes[edit | edit source]

A naming convention for classes draws a hard line between object-oriented abstractions and other kinds of abstractions. Given that engineers have been defining abstract data types in Ada 83 (Ada Reference Manual 1983) for over 10 years, you may not want to change the naming convention just for the sake of using type extension with a type. You must consider how important it is to call out uses of inheritance in the overall use of abstractions in your program. If you prefer to emphasize abstraction, in general, over the mechanism used to implement the abstraction (i.e., inheritance, type-extension, and polymorphism), you may not want to impose such a stringent naming convention. You do not hamper quality by favoring a smoother transition in naming conventions from abstractions developed without inheritance to those developed with inheritance.

If you choose a naming convention that highlights the use of object-oriented features and later decide to change the declaration to one that does not use an object-oriented feature, the change may be expensive. You must naturally change all occurrences of the names and must be careful not to introduce errors as you update the names. If you choose a naming convention that prohibits the use of suffixes or prefixes to characterize the declaration, you lose the opportunity to convey the intended usage of the declared item.

Program Unit Names[edit | edit source]

guideline[edit | edit source]

  • Use action verbs for procedures and entries.
  • Use predicate clauses for Boolean functions.
  • Use nouns for non-Boolean functions.
  • Give packages names that imply a higher level of organization than subprograms. Generally, these are noun phrases that describe the abstraction provided.
  • Give tasks names that imply an active entity.
  • Use nouns descriptive of the data being protected for protected units.
  • Consider naming generic subprograms as if they were nongeneric subprograms.
  • Consider naming generic packages as if they were nongeneric packages.
  • Make the generic names more general than the instantiated names.

example[edit | edit source]

The following are sample names for elements that compose an Ada program:

Sample procedure names:

procedure Get_Next_Token          -- get is a transitive verb
procedure Create                  -- create is a transitive verb

Sample function names for Boolean-valued functions:

function Is_Last_Item             -- predicate clause
function Is_Empty                 -- predicate clause

Sample function names for non-Boolean-valued functions:

function Successor                -- common noun
function Length                   -- attribute
function Top                      -- component

Sample package names:

package Terminals is               -- common noun
package Text_Routines is           -- common noun

Sample protected objects:

protected Current_Location is      -- data being protected
protected type Guardian is         -- noun implying protection

Sample task names:

task Terminal_Resource_Manager is  -- common noun that shows action

The following sample piece of code shows the clarity that results from using the parts-of-speech naming conventions:

Get_Next_Token(Current_Token);

case Current_Token is
   when Identifier =>         Process_Identifier;
   when Numeric    =>         Process_Numeric;
end case;  -- Current_Token

if Is_Empty(Current_List) then
   Number_Of_Elements := 0;
else
   Number_Of_Elements := Length(Current_List);
end if;

When packages and their subprograms are named together, the resulting code is very descriptive:

if Stack.Is_Empty(Current_List) then
   Current_Token := Stack.Top(Current_List);
end if;

rationale[edit | edit source]

Using these naming conventions creates understandable code that reads much like natural language. When verbs are used for actions, such as subprograms, and nouns are used for objects, such as the data that the subprogram manipulates, code is easier to read and understand. This models a medium of communication already familiar to a reader. Where the pieces of a program model a real-life situation, using these conventions reduces the number of translation steps involved in reading and understanding the program. In a sense, your choice of names reflects the level of abstraction from computer hardware toward application requirements.

See also Guideline 3.2.4 for the use of special-purpose suffixes in packages associated with tagged types.

notes[edit | edit source]

There are some conflicting conventions in current use for task entries. Some programmers and designers advocate naming task entries with the same conventions used for subprograms to blur the fact that a task is involved. Their reasoning is that if the task is reimplemented as a package, or vice versa, the names need not change. Others prefer to make the fact of a task entry as explicit as possible to ensure that the existence of a task with its presumed overhead is recognizable. Project-specific priorities may be useful in choosing between these conventions.

Constants and Named Numbers[edit | edit source]

guideline[edit | edit source]

  • Use symbolic values instead of literals where the symbolic value improves readability.
  • Use symbolic values instead of literals if the value occurs at more than one place and might need to be changed.
  • Use the predefined constants Ada.Numerics.Pi and Ada.Numerics.e for the mathematical constants Pi and e.
  • Use constants instead of variables for constant values.
  • Use a constant when the value is specific to a type or when the value must be static.
  • Use named numbers instead of constants, whenever possible.
  • Use named numbers to replace numeric literals whose type or context is truly universal.
  • Use constants for objects whose values cannot change after elaboration (United Technologies 1987).
  • Show relationships between symbolic values by defining them with static expressions.
  • Use linearly independent sets of literals.
  • Use attributes like 'First and 'Last instead of literals, wherever possible.

example[edit | edit source]

3.14159_26535_89793                                 -- literal
Max_Entries : constant Integer       := 400;        -- constant
Avogadros_Number  : constant := 6.022137 * 10**23;  -- named number
Avogadros_Number / 2                                -- static expression
Avogadros_Number                                    -- symbolic value

Declaring Pi as a named number (assuming a with clause for the predefined package Ada.Numerics in the Ada Reference Manual 1995, §A.5 [Annotated] allows it to be referenced symbolically in the assignment statement below:

Area :=       Pi * Radius**2;       -- if radius is known.

instead of:

Area := 3.14159 * Radius**2;        -- Needs explanatory comment

Also, Ada.Characters.Latin_1.Bel is more expressive than Character'Val(8#007#).

Clarity of constant and named number declarations can be improved by using other constant and named numbers. For example:

Bytes_Per_Page   : constant := 512;
Pages_Per_Buffer : constant := 10;
Buffer_Size      : constant := Pages_Per_Buffer * Bytes_Per_Page;

is more self-explanatory and easier to maintain than:

Buffer_Size : constant := 5_120;   -- ten pages

The following literals should be constants:

if New_Character  = '$' then  -- "constant" that may change
...
if Current_Column = 7 then    -- "constant" that may change

rationale[edit | edit source]

Using identifiers instead of literals makes the purpose of expressions clear, reducing the need for comments. Constant declarations consisting of expressions of numeric literals are safer because they do not need to be computed by hand. They are also more enlightening than a single numeric literal because there is more opportunity for embedding explanatory names. Clarity of constant declarations can be improved further by using other related constants in static expressions defining new constants. This is not less efficient because static expressions of named numbers are computed at compile time.

A constant has a type. A named number can only be a universal type: universal_integer or universal_real. Strong typing is enforced for constants but not for named numbers or literals. Named numbers allow compilers to generate more efficient code than for constants and to perform more complete error checking at compile time. If the literal contains a large number of digits (as Pi in the example above), the use of an identifier reduces keystroke errors. If keystroke errors occur, they are easier to locate either by inspection or at compile time.

Independence of literals means that the few literals that are used do not depend on one another and that any relationship between constant or named values is shown in the static expressions. Linear independence of literal values gives the property that if one literal value changes, all of the named numbers of values dependent on that literal are automatically changed.

See Guideline 4.1.4 for additional guidelines on choosing a parameterless function versus a constant.

notes[edit | edit source]

There are situations where a literal is a better choice than a name. For this to be the case, the following conditions have to be fulfilled:

  • The literal has to be self-explanatory in the respective context, such that replacing the literal by a symbolic value would not improve the readability.
  • The value is either unchangeable or only occurs at one single place in the code, such that replacing the literal by a symbolic value would not improve the maintainability.

For example, the literals in the following well known relationship are both self-explanatory and unchangeable:

   Fahrenheit := 32.0 + (9.0 * Celsius) / 5.0;

As a second example, dividing by the literal 2 is self-explanatory in a binary search algorithm context. And, since the value is also unchangeably related with the algorithm, it also does not matter if the literal occurs at more than one place in the code (for example due to loop unrolling). Therefore, the use of a symbolic value like the following would neither improve readability nor maintainability:

   Binary_Search_Divisor : constant := 2;

Exceptions[edit | edit source]

guideline[edit | edit source]

  • Use a name that indicates the kind of problem the exception represents.

example[edit | edit source]

Invalid_Name: exception;
Stack_Overflow: exception;

rationale[edit | edit source]

Naming exceptions according to the kind of problem they are detecting enhances the readability of the code. You should name your exceptions as precisely as you can so that the maintainer of the code understands why the exception might be raised. A well-named exception should be meaningful to the clients of the package declaring the exception.

Constructors[edit | edit source]

guideline[edit | edit source]

  • Include a prefix like New, Make, or Create in naming constructors (in this sense, operations to create and/or initialize an object).
  • Use names indicative of their content for child packages containing constructors.

instantiation[edit | edit source]

  • Name a child package containing constructors <whatever>.Constructor.

example[edit | edit source]

function Make_Square (Center : Cartesian_Coordinates; 
                      Side   : Positive)
  return Square;

rationale[edit | edit source]

Including a word like New, Make, or Create in a constructor name makes its purpose clear. You may want to restrict the use of the prefix New to constructors that return an access value because the prefix suggests the internal use of an allocator.

Putting all constructors in a child package, even when they return access values, is a useful organizational principle.

For information regarding the use of Ada constructors, refer to Guideline 9.3.3.

Comments[edit | edit source]

Comments in source text are a controversial issue. There are arguments both for and against the view that comments enhance readability. In practice, the biggest problem with comments is that people often fail to update them when the associated source text is changed, thereby making the commentary misleading. Commentary should be reserved for expressing needed information that cannot be expressed in code and highlighting cases where there are overriding reasons to violate one of the guidelines. If possible, source text should use self-explanatory names for objects and program units, and it should use simple, understandable program structures so that little additional commentary is needed. The extra effort in selecting (and entering) appropriate names and the extra thought needed to design clean and understandable program structures are fully justified.

Use comments to state the intent of the code. Comments that provide an overview of the code help the maintenance programmer see the forest for the trees. The code itself is the detailed "how" and should not be paraphrased in the comments.

Comments should be minimized. They should provide needed information that cannot be expressed in the Ada language, emphasize the structure of code, and draw attention to deliberate and necessary violations of the guidelines. Comments are present either to draw attention to the real issue being exemplified or to compensate for incompleteness in the sample program.

Maintenance programmers need to know the causal interaction of noncontiguous pieces of code to get a global, more or less complete sense of the program. They typically acquire this kind of information from mental simulation of parts of the code. Comments should be sufficient enough to support this process (Soloway et al. 1986).

This section presents general guidelines about how to write good comments. It then defines several different classes of comments with guidelines for the use of each. The classes are file headers, program unit specification headers, program unit body headers, data comments, statement comments, and marker comments.

General Comments[edit | edit source]

guideline[edit | edit source]

  • Make the code as clear as possible to reduce the need for comments.
  • Never repeat information in a comment that is readily available in the code.
  • Where a comment is required, make it concise and complete.
  • Use proper grammar and spelling in comments.
  • Make comments visually distinct from the code.
  • Structure comments in header so that information can be automatically extracted by a tool.

rationale[edit | edit source]

The structure and function of well-written code is clear without comments. Obscured or badly structured code is hard to understand, maintain, or reuse regardless of comments. Bad code should be improved, not explained. Reading the code itself is the only way to be absolutely positive about what the code does; therefore, the code should be made as readable as possible.

Using comments to duplicate information in the code is a bad idea for several reasons. First, it is unnecessary work that decreases productivity. Second, it is very difficult to correctly maintain the duplication as the code is modified. When changes are made to existing code, it is compiled and tested to make sure that it is once again correct. However, there is no automatic mechanism to make sure that the comments are correctly updated to reflect the changes. Very often, the duplicate information in a comment becomes obsolete at the first code change and remains so through the life of the software. Third, when comments about an entire system are written from the limited point of view of the author of a single subsystem, the comments are often incorrect from the start.

Comments are necessary to reveal information difficult or impossible to obtain from the code. Subsequent chapters of this book contain examples of such comments. Completely and concisely present the required information.

The purpose of comments is to help readers understand the code. Misspelled, ungrammatical, ambiguous, or incomplete comments defeat this purpose. If a comment is worth adding, it is worth adding correctly in order to increase its usefulness.

Making comments visually distinct from the code by indenting them, grouping them together into headers, or highlighting them with dashed lines is useful because it makes the code easier to read. Subsequent chapters of this book elaborate on this point.

automation notes[edit | edit source]

The guideline about storing redundant information in comments applies only to manually generated comments. There are tools that automatically maintain information about the code (e.g., calling units, called units, cross-reference information, revision histories, etc.), storing it in comments in the same file as the code. Other tools read comments but do not update them, using the information from the comments to automatically generate detailed design documents and other reports.

The use of such tools is encouraged and may require that you structure your header comments so they can be automatically extracted and/or updated. Beware that tools that modify the comments in a file are only useful if they are executed frequently enough. Automatically generated obsolete information is even more dangerous than manually generated obsolete information because it is more trusted by the reader.

Revision histories are maintained much more accurately and completely by configuration management tools. With no tool support, it is very common for an engineer to make a change and forget to update the revision history. If your configuration management tool is capable of maintaining revision histories as comments in the source file, then take advantage of that capability, regardless of any compromise you might have to make about the format or location of the revision history. It is better to have a complete revision history appended to the end of the file than to have a partial one formatted nicely and embedded in the file header.

File Headers[edit | edit source]

guideline[edit | edit source]

  • Put a file header on each source file.
  • Place ownership, responsibility, and history information for the file in the file header.

instantiation[edit | edit source]

  • Put a copyright notice in the file header.
  • Put the author's name and department in the file header.
  • Put a revision history in the file header, including a summary of each change, the date, and the name of the person making the change.

example[edit | edit source]

------------------------------------------------------------------------
--      Copyright (c) 1991, Software Productivity Consortium, Inc.
--      All rights reserved.
--
-- Author: J. Smith
-- Department:System Software Department
--
-- Revision History:
--   7/9/91 J. Smith
--     - Added function Size_Of to support queries of node sizes.
--     - Fixed bug in Set_Size which caused overlap of large nodes.
--   7/1/91 M. Jones
--     - Optimized clipping algorithm for speed.
--   6/25/91 J. Smith
--     - Original version.
------------------------------------------------------------------------

rationale[edit | edit source]

Ownership information should be present in each file if you want to be sure to protect your rights to the software. Furthermore, for high visibility, it should be the first thing in the file.

Responsibility and revision history information should be present in each file for the sake of future maintainers; this is the header information most trusted by maintainers because it accumulates. It does not evolve. There is no need to ever go back and modify the author's name or the revision history of a file. As the code evolves, the revision history should be updated to reflect each change. At worst, it will be incomplete; it should rarely be wrong. Also, the number and frequency of changes and the number of different people who made the changes over the history of a unit can be good indicators of the integrity of the implementation with respect to the design.

Information about how to find the original author should be included in the file header, in addition to the author's name, to make it easier for maintainers to find the author in case questions arise. However, detailed information like phone numbers, mail stops, office numbers, and computer account user names are too volatile to be very useful. It is better to record the department for which the author was working when the code was written. This information is still useful if the author moves offices, changes departments, or even leaves the company because the department is likely to retain responsibility for the original version of the code.

notes[edit | edit source]

With modern configuration management systems, explicitly capturing version history as header comments may be superfluous. The configuration management tool maintains a more reliable and consistent (from a content point of view) change history. Some systems can re-create earlier versions of a unit.

Program Unit Specification Headers[edit | edit source]

guideline[edit | edit source]

  • Put a header on the specification of each program unit.
  • Place information required by the user of the program unit in the specification header.
  • Do not repeat information (except unit name) in the specification header that is present in the specification.
  • Explain what the unit does, not how or why it does it.
  • Describe the complete interface to the program unit, including any exceptions it can raise and any global effects it can have.
  • Do not include information about how the unit fits into the enclosing software system.
  • Describe the performance (time and space) characteristics of the unit.

instantiation[edit | edit source]

  • Put the name of the program unit in the header.
  • Briefly explain the purpose of the program unit.
  • For packages, describe the effects of the visible subprograms on each other and how they should be used together.
  • List all exceptions that can be raised by the unit.
  • List all global effects of the unit.
  • List preconditions and postconditions of the unit.
  • List hidden tasks activated by the unit.
  • Do not list the names of parameters of a subprogram.
  • Do not list the names of package subprograms just to list them.
  • Do not list the names of all other units used by the unit.
  • Do not list the names of all other units that use the unit.

example[edit | edit source]

     ------------------------------------------------------------------------
     -- AUTOLAYOUT
     --
     -- Purpose:
     --   This package computes positional information for nodes and arcs
     --   of a directed graph.  It encapsulates a layout algorithm which is
     --   designed to minimize the number of crossing arcs and to emphasize
     --   the primary direction of arc flow through the graph.
     --
     -- Effects:
     --   - The expected usage is:
     --     1. Call Define for each node and arc to define the graph.
     --     2. Call Layout to assign positions to all nodes and arcs.
     --     3. Call Position_Of for each node and arc to determine the
     --        assigned coordinate positions.
     --   - Layout can be called multiple times, and recomputes the
     --     positions of all currently defined nodes and arcs each time.
     --   - Once a node or arc has been defined, it remains defined until
     --     Clear is called to delete all nodes and arcs.
     --
     -- Performance:
     --   This package has been optimized for time, in preference to space.
     --   Layout times are on the order of N*log(N) where N is the number
     --   of nodes, but memory space is used inefficiently.
     ------------------------------------------------------------------------

     package Autolayout is

        ...

        ---------------------------------------------------------------------
        -- Define
        --
        -- Purpose:
        --   This procedure defines one node of the current graph.
        -- Exceptions:
        --   Node_Already_Defined
        ---------------------------------------------------------------------
        procedure Define
              (New_Node : in     Node);

        ---------------------------------------------------------------------
        -- Layout
        --
        -- Purpose:
        --   This procedure assigns coordinate positions to all defined
        --   nodes and arcs.
        -- Exceptions:
        --   None.
        ---------------------------------------------------------------------
        procedure Layout;

        ---------------------------------------------------------------------
        -- Position_Of
        --
        -- Purpose:
        --   This function returns the coordinate position of the
        --   specified node.  The default position (0,0) is returned if no
        --   position has been assigned yet.
        -- Exceptions:
        --   Node_Not_Defined
        ---------------------------------------------------------------------
        function Position_Of (Current : in     Node)
              return Position;

        ...

     end Autolayout;

rationale[edit | edit source]

The purpose of a header comment on the specification of a program unit is to help the user understand how to use the program unit. From reading the program unit specification and header, a user should know everything necessary to use the unit. It should not be necessary to read the body of the program unit. Therefore, there should be a header comment on each program unit specification, and each header should contain all usage information not expressed in the specification itself. Such information includes the units' effects on each other and on shared resources, exceptions raised, and time/space characteristics. None of this information can be determined from the Ada specification of the program unit.

When you duplicate information in the header that can be readily obtained from the specification, the information tends to become incorrect during maintenance. For example, do not make a point of listing all parameter names, modes, or subtypes when describing a procedure. This information is already available from the procedure specification. Similarly, do not list all subprograms of a package in the header unless this is necessary to make some important statement about the subprograms.

Do not include information in the header that the user of the program unit does not need. In particular, do not include information about how a program unit performs its function or why a particular algorithm was used. This information should be hidden in the body of the program unit to preserve the abstraction defined by the unit. If the user knows such details and makes decisions based on that information, the code may suffer when that information is later changed.

When describing the purpose of the unit, avoid referring to other parts of the enclosing software system. It is better to say "this unit does…" than to say "this unit is called by Xyz to do…." The unit should be written in such a way that it does not know or care which unit is calling it. This makes the unit much more general purpose and reusable. In addition, information about other units is likely to become obsolete and incorrect during maintenance.

Include information about the performance (time and space) characteristics of the unit. Much of this information is not present in the Ada specification, but it is required by the user. To integrate the unit into a system, the user needs to understand the resource usage (CPU, memory, etc.) of the unit. It is especially important to note that when a subprogram call causes activation of a task hidden in a package body, the task may continue to consume resources after the subroutine ends.

notes[edit | edit source]

Some projects have deferred most of the commentary to the end rather than at the beginning of the program unit. Their rationale is that program units are written once and read many times and that long header comments make the start of the specification difficult to find.

exceptions[edit | edit source]

Where a group of program units are closely related or simple to understand, it is acceptable to use a single header for the entire group of program units. For example, it makes sense to use a single header to describe the behavior of Max and Min functions; Sin, Cos, and Tan functions; or a group of functions to query related attributes of an object encapsulated in a package. This is especially true when each function in the set is capable of raising the same exceptions.

Program Unit Body Headers[edit | edit source]

guideline[edit | edit source]

  • Place information required by the maintainer of the program unit in the body of the header
  • Explain how and why the unit performs its function, not what the unit does.
  • Do not repeat information (except unit name) in the header that is readily apparent from reading the code.
  • Do not repeat information (except unit name) in the body header that is available in the specification header.

instantiation[edit | edit source]

  • Put the name of the program unit in the header.
  • Record portability issues in the header.
  • Summarize complex algorithms in the header.
  • Record reasons for significant or controversial implementation decisions.
  • Record discarded implementation alternatives, along with the reason for discarding them.
  • Record anticipated changes in the header, especially if some work has already been done to the code to make the changes easy to accomplish.

example[edit | edit source]

------------------------------------------------------------------------
-- Autolayout
--
-- Implementation Notes:
--   - This package uses a heuristic algorithm to minimize the number
--     of arc crossings.  It does not always achieve the true minimum
--     number which could theoretically be reached.  However it does a
--     nearly perfect job in relatively little time.  For details about
--     the algorithm, see ...
--
-- Portability Issues:
--   - The native math package Math_Lib is used for computations of
--     coordinate positions.
--   - 32-bit integers are required.
--   - No operating system specific routines are called.
--
-- Anticipated Changes:
--   - Coordinate_Type below could be changed from integer to float
--     with little effort.  Care has been taken to not depend on the
--     specific characteristics of integer arithmetic.
------------------------------------------------------------------------
package body Autolayout is

   ...

   ---------------------------------------------------------------------
   -- Define
   --
   -- Implementation Notes:
   --   - This routine stores a node in the general purpose Graph data
   --     structure, not the Fast_Graph structure because ...
   ---------------------------------------------------------------------
   procedure Define
         (New_Node : in     Node) is
   begin
      ...
   end Define;

   ---------------------------------------------------------------------
   -- Layout
   --
   -- Implementation Notes:
   --   - This routine copies the Graph data structure (optimized for
   --     fast random access) into the Fast_Graph data structure
   --     (optimized for fast sequential iteration), then performs the
   --     layout, and copies the data back to the Graph structure.  This
   --     technique was introduced as an optimization when the algorithm
   --     was found to be too slow, and it produced an order of
   --     magnitude improvement.
   ---------------------------------------------------------------------
   procedure Layout is
   begin
      ...
   end Layout;

   ---------------------------------------------------------------------
   -- Position_Of
   ---------------------------------------------------------------------
   function Position_Of (Current : in     Node)
         return Position is
   begin
      ...
   end Position_Of;

   ...

end Autolayout;

rationale[edit | edit source]

The purpose of a header comment on the body of a program unit is to help the maintainer of the program unit to understand the implementation of the unit, including tradeoffs among different techniques. Be sure to document all decisions made during implementation to prevent the maintainer from making the same mistakes you made. One of the most valuable comments to a maintainer is a clear description of why a change being considered will not work.

The header is also a good place to record portability concerns. The maintainer may have to port the software to a different environment and will benefit from a list of nonportable features. Furthermore, the act of collecting and recording portability issues focuses attention on these issues and may result in more portable code from the start.

Summarize complex algorithms in the header if the code is difficult to read or understand without such a summary, but do not merely paraphrase the code. Such duplication is unnecessary and hard to maintain. Similarly, do not repeat the information from the header of the program unit specification.

notes[edit | edit source]

It is often the case that a program unit is self-explanatory so that it does not require a body header to explain how it is implemented or why. In such a case, omit the header entirely, as in the case with Position_Of above. Be sure, however, that the header you omit truly contains no information. For example, consider the difference between the two header sections:

-- Implementation Notes:  None.

and:

-- NonPortable Features:  None.

The first is a message from the author to the maintainer saying "I can't think of anything else to tell you," while the second may mean "I guarantee that this unit is entirely portable."

Data Comments[edit | edit source]

guideline[edit | edit source]

  • Comment on all data types, objects, and exceptions unless their names are self-explanatory.
  • Include information on the semantic structure of complex, pointer-based data structures.
  • Include information about relationships that are maintained between data objects.
  • Omit comments that merely repeat the information in the name.
  • Include information on redispatching for tagged types in cases where you intend the specializations (i.e., derived types) to override these redispatching operations.

example[edit | edit source]

Objects can be grouped by purpose and commented as:

...

---------------------------------------------------------------------
-- Current position of the cursor in the currently selected text
-- buffer, and the most recent position explicitly marked by the
-- user.
-- Note:  It is necessary to maintain both current and desired
--        column positions because the cursor cannot always be
--        displayed in the desired position when moving between
--        lines of different lengths.
---------------------------------------------------------------------
Desired_Column : Column_Counter;
Current_Column : Column_Counter;
Current_Row    : Row_Counter;
Marked_Column  : Column_Counter;
Marked_Row     : Row_Counter;

The conditions under which an exception is raised should be commented:

---------------------------------------------------------------------
-- Exceptions
---------------------------------------------------------------------
Node_Already_Defined : exception;   -- Raised when an attempt is made
                                    --|   to define a node with an
                                    --|   identifier which already
                                    --|   defines a node.
Node_Not_Defined     : exception;   -- Raised when a reference is
                                    --|   made to a node which has
                                    --|   not been defined.

Here is a more complex example, involving multiple record and access types that are used to form a complex data structure:

---------------------------------------------------------------------
-- These data structures are used to store the graph during the
-- layout process. The overall organization is a sorted list of
-- "ranks," each containing a sorted list of nodes, each containing
-- a list of incoming arcs and a list of outgoing arcs.
-- The lists are doubly linked to support forward and backward
-- passes for sorting. Arc lists do not need to be doubly linked
-- because order of arcs is irrelevant.
--
-- The nodes and arcs are doubly linked to each other to support
-- efficient lookup of all arcs to/from a node, as well as efficient
-- lookup of the source/target node of an arc.
---------------------------------------------------------------------

type Arc;
type Arc_Pointer is access Arc;

type Node;
type Node_Pointer is access Node;

type Node is
   record
      Id       : Node_Pointer;-- Unique node ID supplied by the user.
      Arc_In   : Arc_Pointer;
      Arc_Out  : Arc_Pointer;
      Next     : Node_Pointer;
      Previous : Node_Pointer;
   end record;

type Arc is
   record
      ID     : Arc_ID;        -- Unique arc ID supplied by the user.
      Source : Node_Pointer;
      Target : Node_Pointer;
      Next   : Arc_Pointer;
   end record;

type Rank;
type Rank_Pointer is access Rank;

type Rank is
   record
      Number     : Level_ID;  -- Computed ordinal number of the rank.
      First_Node : Node_Pointer;
      Last_Node  : Node_Pointer;
      Next       : Rank_Pointer;
      Previous   : Rank_Pointer;
   end record;

First_Rank : Rank_Pointer;
Last_Rank  : Rank_Pointer;

rationale[edit | edit source]

It is very useful to add comments explaining the purpose, structure, and semantics of the data structures. Many maintainers look at the data structures first when trying to understand the implementation of a unit. Understanding the data that can be stored, along with the relationships between the different data items and the flow of data through the unit, is an important first step in understanding the details of the unit.

In the first example above, the names Current_Column and Current_Row are relatively self-explanatory. The name Desired_Column is also well chosen, but it leaves the reader wondering what the relationship is between the current column and the desired column. The comment explains the reason for having both.

Another advantage of commenting on the data declarations is that the single set of comments on a declaration can replace multiple sets of comments that might otherwise be needed at various places in the code where the data is manipulated. In the first example above, the comment briefly expands on the meaning of "current" and "marked." It states that the "current" position is the location of the cursor, the "current" position is in the current buffer, and the "marked" position was marked by the user. This comment, along with the mnemonic names of the variables, greatly reduces the need for comments at individual statements throughout the code.

It is important to document the full meaning of exceptions and under what conditions they can be raised, as shown in the second example above, especially when the exceptions are declared in a package specification. The reader has no other way to find out the exact meaning of the exception (without reading the code in the package body).

Grouping all the exceptions together, as shown in the second example, can provide the reader with the effect of a "glossary" of special conditions. This is useful when many different subprograms in the package can raise the same exceptions. For a package in which each exception can be raised by only one subprogram, it may be better to group related subprograms and exceptions together.

When commenting exceptions, it is better to describe the exception's meaning in general terms than to list all the subprograms that can cause the exception to be raised; such a list is harder to maintain. When a new routine is added, it is likely that these lists will not be updated. Also, this information is already present in the comments describing the subprograms, where all exceptions that can be raised by the subprogram should be listed. Lists of exceptions by subprogram are more useful and easier to maintain than lists of subprograms by exception.

In the third example, the names of the record fields are short and mnemonic, but they are not completely self-explanatory. This is often the case with complex data structures involving access types. There is no way to choose the record and field names so that they completely explain the overall organization of the records and pointers into a nested set of sorted lists. The comments shown are useful in this case. Without them, the reader would not know which lists are sorted, which lists are doubly linked, or why. The comments express the intent of the author with respect to this complex data structure. The maintainer still has to read the code if he wants to be sure that the double links are all properly maintained. Keeping this in mind when reading the code makes it much easier for the maintainer to find a bug where one pointer is updated and the opposite one is not.

See Guideline 9.3.1 for the rationale for documenting the use of redispatching operations. (Redispatching means converting an argument of one primitive operation to a class-wide type and making a dispatching call to another primitive operation.) The rationale in Guideline 9.3.1 discusses whether such documentation should be in the specification or the body.

Statement Comments[edit | edit source]

guideline[edit | edit source]

  • Minimize comments embedded among statements.
  • Use comments only to explain parts of the code that are not obvious.
  • Comment intentional omissions from the code.
  • Do not use comments to paraphrase the code.
  • Do not use comments to explain remote pieces of code, such as subprograms called by the current unit.
  • Where comments are necessary, make them visually distinct from the code.

example[edit | edit source]

The following is an example of very poorly commented code:

...

-- Loop through all the strings in the array Strings, converting
-- them to integers by calling Convert_To_Integer on each one,
-- accumulating the sum of all the values in Sum, and counting them
-- in Count.  Then divide Sum by Count to get the average and store
-- it in Average. Also, record the maximum number in the global
-- variable Max_Number.

for I in Strings'Range loop
   -- Convert each string to an integer value by looping through
   -- the characters which are digits, until a nondigit is found,
   -- taking the ordinal value of each, subtracting the ordinal value
   -- of '0', and multiplying by 10 if another digit follows.  Store
   -- the result in Number.
   Number := Convert_To_Integer(Strings(I));
   -- Accumulate the sum of the numbers in Total.
   Sum := Sum + Number;
   -- Count the numbers.
   Count := Count + 1;

   -- Decide whether this number is more than the current maximum.
   if Number > Max_Number then
      -- Update the global variable Max_Number.
      Max_Number := Number;
   end if;

end loop;
-- Compute the average.
Average := Sum / Count;

The following is improved by not repeating things in the comments that are obvious from the code, not describing the details of what goes in inside of Convert_To_Integer, deleting an erroneous comment (the one on the statement that accumulates the sum), and making the few remaining comments more visually distinct from the code.

Sum_Integers_Converted_From_Strings:
   for I in Strings'Range loop
      Number := Convert_To_Integer(Strings(I));
      Sum := Sum + Number;
      Count := Count + 1;

      -- The global Max_Number is computed here for efficiency.
      if Number > Max_Number then
         Max_Number := Number;
      end if;

   end loop Sum_Integers_Converted_From_Strings;

Average := Sum / Count;

rationale[edit | edit source]

The improvements shown in the example are not improvements merely by reducing the total number of comments; they are improvements by reducing the number of useless comments.

Comments that paraphrase or explain obvious aspects of the code have no value. They are a waste of effort for the author to write and the maintainer to update. Therefore, they often end up becoming incorrect. Such comments also clutter the code, hiding the few important comments.

Comments describing what goes on inside another unit violate the principle of information hiding. The details about Convert_To_Integer (deleted above) are irrelevant to the calling unit, and they are better left hidden in case the algorithm ever changes. Examples explaining what goes on elsewhere in the code are very difficult to maintain and almost always become incorrect at the first code modification.

The advantage of making comments visually distinct from the code is that it makes the code easier to scan, and the few important comments stand out better. Highlighting unusual or special code features indicates that they are intentional. This assists maintainers by focusing attention on code sections that are likely to cause problems during maintenance or when porting the program to another implementation.

Comments should be used to document code that is nonportable, implementation-dependent, environment-dependent, or tricky in any way. They notify the reader that something unusual was put there for a reason. A beneficial comment would be one explaining a work around for a compiler bug. If you use a lower level (not "ideal" in the software engineering sense) solution, comment on it. Information included in the comments should state why you used that particular construct. Also include documentation on the failed attempts, for example, using a higher level structure. This kind of comment is useful to maintainers for historical purposes. You show the reader that a significant amount of thought went into the choice of a construct.

Finally, comments should be used to explain what is not present in the code as well as what is present. If you make a conscious decision to not perform some action, like deallocating a data structure with which you appear to be finished, be sure to add a comment explaining why not. Otherwise, a maintainer may notice the apparent omission and "correct" it later, thus introducing an error.

See also Guideline 9.3.1 for a discussion of what kind of documentation you should provide regarding tagged types and redispatching.

notes[edit | edit source]

Further improvements can be made on the above example by declaring the variables Count and Sum in a local block so that their scope is limited and their initializations occur near their usage, e.g., by naming the block Compute_Average or by moving the code into a function called Average_Of. The computation of Max_Number can also be separated from the computation of Average. However, those changes are the subject of other guidelines; this example is only intended to illustrate the proper use of comments.

Marker Comments[edit | edit source]

guideline[edit | edit source]

  • Use pagination markers to mark program unit boundaries (see Guideline 2.1.7).
  • Repeat the unit name in a comment to mark the begin of a package body, subprogram body, task body, or block if the begin is preceded by declarations.
  • For long or heavily nested if and case statements, mark the end of the statement with a comment summarizing the condition governing the statement.
  • For long or heavily nested if statements, mark the else part with a comment summarizing the conditions governing this portion of the statement.

example[edit | edit source]

if    A_Found then
   ...
elsif B_Found then
   ...

else  -- A and B were both not found
   ...

   if Count = Max then
      ...

   end if;

   ...
end if;  -- A_Found

------------------------------------------------------------------------
package body Abstract_Strings is
   ...

   ---------------------------------------------------------------------
   procedure Concatenate (...) is
   begin
      ...
   end Concatenate;
   ---------------------------------------------------------------------

   ...
begin  -- Abstract_Strings
   ...
end Abstract_Strings;
------------------------------------------------------------------------

rationale[edit | edit source]

Marker comments emphasize the structure of code and make it easier to scan. They can be lines that separate sections of code or descriptive tags for a construct. They help the reader resolve questions about the current position in the code. This is more important for large units than for small ones. A short marker comment fits on the same line as the reserved word with which it is associated. Thus, it adds information without clutter.

The if, elsif, else, and end if of an if statement are often separated by long sequences of statements, sometimes involving other if statements. As shown in the first example, marker comments emphasize the association of the keywords of the same statement over a great visual distance. Marker comments are not necessary with the block statement and loop statement because the syntax of these statements allows them to be named with the name repeated at the end. Using these names is better than using marker comments because the compiler verifies that the names at the beginning and end match.

The sequence of statements of a package body is often very far from the first line of the package. Many subprogram bodies, each containing many begin lines, may occur first. As shown in the second example, the marker comment emphasizes the association of the begin with the package.

notes[edit | edit source]

Repeating names and noting conditional expressions clutters the code if overdone. It is visual distance, especially page breaks, that makes marker comments beneficial.

Using Types[edit | edit source]

Strong typing promotes reliability in software. The type definition of an object defines all legal values and operations and allows the compiler to check for and identify potential errors during compilation. In addition, the rules of type allow the compiler to generate code to check for violations of type constraints at execution time. Using these Ada compiler's features facilitates earlier and more complete error detection than that which is available with less strongly typed languages.

Declaring Types[edit | edit source]

guideline[edit | edit source]

  • Limit the range of scalar types as much as possible.
  • Seek information about possible values from the application.
  • Do not reuse any of the subtype names in package Standard.
  • Use subtype declarations to improve program readability (Booch 1987).
  • Use derived types and subtypes in concert (see Guideline 5.3.1).

example[edit | edit source]

subtype Card_Image is String (1 .. 80);
Input_Line : Card_Image := (others => ' ');
-- restricted integer type:
type    Day_Of_Leap_Year     is                  range 1 .. 366;
subtype Day_Of_Non_Leap_Year is Day_Of_Leap_Year range 1 .. 365;

By the following declaration, the programmer means, "I haven't the foggiest idea how many," but the actual base range will show up buried in the code or as a system parameter:

Employee_Count : Integer;

rationale[edit | edit source]

Eliminating meaningless values from the legal range improves the compiler's ability to detect errors when an object is set to an invalid value. This also improves program readability. In addition, it forces you to carefully think about each use of objects declared to be of the subtype.

Different implementations provide different sets of values for most of the predefined types. A reader cannot determine the intended range from the predefined names. This situation is aggravated when the predefined names are overloaded.

The names of an object and its subtype can clarify their intended use and document low-level design decisions. The example above documents a design decision to restrict the software to devices whose physical parameters are derived from the characteristics of punch cards. This information is easy to find for any later changes, thus enhancing program maintainability.

You can rename a type by declaring a subtype without a constraint (Ada Reference Manual 1995, §8.5 [Annotated]). You cannot overload a subtype name; overloading only applies to callable entities. Enumeration literals are treated as parameterless functions and so are included in this rule.

Types can have highly constrained sets of values without eliminating useful values. Usage as described in Guideline 5.3.1 eliminates many flag variables and type conversions within executable statements. This renders the program more readable while allowing the compiler to enforce strong typing constraints.

notes[edit | edit source]

Subtype declarations do not define new types, only constraints for existing types.

Any deviation from this guideline detracts from the advantages of the strong typing facilities of the Ada language.

exceptions[edit | edit source]

There are cases where you do not have a particular dependence on any range of numeric values. Such situations occur, for example, with array indices (e.g., a list whose size is not fixed by any particular semantics). See Guideline 7.2.1 for a discussion of appropriate uses of predefined types.

Enumeration Types[edit | edit source]

guideline[edit | edit source]

  • Use enumeration types instead of numeric codes.
  • Only if absolutely necessary, use representation clauses to match requirements of external devices.

example[edit | edit source]

Use:

type Color is (Blue, Red, Green, Yellow);

rather than:

Blue   : constant := 1;
Red    : constant := 2;
Green  : constant := 3;
Yellow : constant := 4;

and add the following if necessary:

for Color use (Blue   => 1,
               Red    => 2,
               Green  => 3,
               Yellow => 4);

rationale[edit | edit source]

Enumerations are more robust than numeric codes; they leave less potential for errors resulting from incorrect interpretation and from additions to and deletions from the set of values during maintenance. Numeric codes are holdovers from languages that have no user-defined types.

In addition, Ada provides a number of attributes ('Pos, 'Val, 'Succ, 'Pred, 'Image, and 'Value) for enumeration types that, when used, are more reliable than user-written operations on encodings.

A numeric code may at first seem appropriate to match external values. Instead, these situations call for a representation clause on the enumeration type. The representation clause documents the "encoding." If the program is properly structured to isolate and encapsulate hardware dependencies (see Guideline 7.1.5), the numeric code ends up in an interface package where it can be easily found and replaced if the requirements change.

In general, avoid using representation clauses for enumeration types. When there is no obvious ordering of the enumeration literals, an enumeration representation can create portability problems if the enumeration type must be reordered to accommodate a change in representation order on the new platform.

Summary[edit | edit source]

spelling[edit | edit source]

  • Use underscores to separate words in a compound name.
  • Represent numbers in a consistent fashion.
  • Represent literals in a radix appropriate to the problem.
  • Use underscores to separate digits the same way commas or periods (or spaces for nondecimal bases) would be used in normal text.
  • When using scientific notation, make the E consistently either uppercase or lowercase.
  • In an alternate base, represent the alphabetic characters in either all uppercase or all lowercase.
  • Make reserved words and other elements of the program visually distinct from each other.
  • Do not use an abbreviation of a long word as an identifier where a shorter synonym exists.
  • Use a consistent abbreviation strategy.
  • Do not use ambiguous abbreviations.
  • To justify its use, an abbreviation must save many characters over the full word.
  • Use abbreviations that are well-accepted in the application domain.
  • Maintain a list of accepted abbreviations, and use only abbreviations on that list.

naming conventions[edit | edit source]

  • Choose names that are as self-documenting as possible.
  • Use a short synonym instead of an abbreviation.
  • Use names given by the application, but do not use obscure jargon.
  • Avoid using the same name to declare different kinds of identifiers.
  • Use singular, general nouns as subtype identifiers.
  • Choose identifiers that describe one of the subtype's values.
  • Consider using suffixes for subtype identifiers that define visible access types, visible subranges, or visible array types.
  • For private types, do not use identifier constructions (e.g., suffixes) that are unique to subtype identifiers.
  • Do not use the subtype names from predefined packages.
  • Use predicate clauses or adjectives for Boolean objects.
  • Use singular, specific nouns as object identifiers.
  • Choose identifiers that describe the object's value during execution.
  • Use singular, general nouns as identifiers for record components.
  • Use a consistent naming convention for tagged types and associated packages.
  • Use action verbs for procedures and entries.
  • Use predicate clauses for Boolean functions.
  • Use nouns for non-Boolean functions.
  • Give packages names that imply a higher level of organization than subprograms. Generally, these are noun phrases that describe the abstraction provided.
  • Give tasks names that imply an active entity.
  • Use nouns descriptive of the data being protected for protected units.
  • Consider naming generic subprograms as if they were nongeneric subprograms.
  • Consider naming generic packages as if they were nongeneric packages.
  • Make the generic names more general than the instantiated names.
  • Use symbolic values instead of literals, wherever possible.
  • Use the predefined constants Ada.Numerics.Pi and Ada.Numerics.e for the mathematical constants Pi and e.
  • Use constants instead of variables for constant values.
  • Use a constant when the value is specific to a type or when the value must be static.
  • Use named numbers instead of constants, whenever possible.
  • Use named numbers to replace numeric literals whose type or context is truly universal.
  • Use constants for objects whose values cannot change after elaboration. (United Technologies 1987).
  • Show relationships between symbolic values by defining them with static expressions.
  • Use linearly independent sets of literals.
  • Use attributes like 'First and 'Last instead of literals, wherever possible.
  • Use a name that indicates the kind of problem the exception represents.
  • Include a prefix like New, Make, or Create in naming constructors (in this sense, operations to create and/or initialize an object).
  • Use names indicative of their content for child packages containing constructors.

comments[edit | edit source]

  • Make the code as clear as possible to reduce the need for comments.
  • Never repeat information in a comment that is readily available in the code.
  • Where a comment is required, make it concise and complete.
  • Use proper grammar and spelling in comments.
  • Make comments visually distinct from the code.
  • Structure comments in headers so that information can be automatically extracted by a tool.
  • Put a file header on each source file.
  • Place ownership, responsibility, and history information for the file in the file header.
  • Put a header on the specification of each program unit.
  • Place information required by the user of the program unit in the specification header.
  • Do not repeat information (except unit name) in the specification header that is present in the specification.
  • Explain what the unit does, not how or why it does it.
  • Describe the complete interface to the program unit, including any exceptions it can raise and any global effects it can have.
  • Do not include information about how the unit fits into the enclosing software system.
  • Describe the performance (time and space) characteristics of the unit.
  • Place information required by the maintainer of the program unit in the body header.
  • Explain how and why the unit performs its function, not what the unit does.
  • Do not repeat information (except unit name) in the header that is readily apparent from reading the code.
  • Do not repeat information (except unit name) in the body header that is available in the specification header.
  • Comment on all data types, objects, and exceptions unless their names are self-explanatory.
  • Include information on the semantic structure of complex, pointer-based data structures.
  • Include information about relationships that are maintained between data objects.
  • Omit comments that merely repeat the information in the name.
  • Include information on redispatching for tagged types in cases where you intend the specializations (i.e., derived types) to override these redispatching operations.
  • Minimize comments embedded among statements.
  • Use comments only to explain parts of the code that are not obvious.
  • Comment intentional omissions from the code.
  • Do not use comments to paraphrase the code.
  • Do not use comments to explain remote pieces of code, such as subprograms called by the current unit.
  • Where comments are necessary, make them visually distinct from the code.
  • Use pagination markers to mark program unit boundaries.
  • Repeat the unit name in a comment to mark the begin of a package body, subprogram body, task body, or block if the begin is preceded by declarations.
  • For long or heavily nested if and case statements, mark the end of the statement with a comment summarizing the condition governing the statement.
  • For long or heavily nested if statements, mark the else part with a comment summarizing the conditions governing this portion of the statement.

using types[edit | edit source]

  • Limit the range of scalar types as much as possible.
  • Seek information about possible values from the application.
  • Do not reuse any of the subtype names in package Standard.
  • Use subtype declarations to improve program readability (Booch 1987).
  • Use derived types and subtypes in concert.
  • Use enumeration types instead of numeric codes.
  • Only if absolutely necessary, use representation clauses to match requirements of external devices.

Program Structure