[net.lang.ada] Ada programmer errors

goodenou@wanginst.UUCP (John Goodenough) (09/23/85)

*** REPLACE THIS LINE WITH YOUR MESSAGE ***
A while ago, I asked people to tell me about common errors made by
experienced or beginning Ada programmers.  I received several responses (one
person sent a lot of helpful material).  I've now summarized the responses
and categorized them by section of the RM.  The next page gives a summary of
the responses by section number, with a brief topical description.  More
detailed information follows.

I'm still interested in hearing from other people on this topic.  If I get
more responses, I'll periodically post updates.  If you have any suggestions
about format, content, etc., let me know.

John B. Goodenough                           goodenou@wanginst        (CSNET)
Wang Institute of Graduate Studies           decvax!wanginst!goodenou (UUCP)
Tyng Road, Tyngsboro, MA 01879               Goodenough@ISI           (ARPA)
(At Wang Institute until 6/1/86)             617-649-9731



			Common Ada Programming Errors

!section 00.00    different uses of =>
!section 00.00    variables set but not referenced, and vice versa
!section 02.03    illegal use of underscore
!section 02.05    one character string literals or character literals
!section 02.09    inadvertant use of reserved words
!section 03.02    anonymous array types
!section 03.02.02 Using non-universal constants in number decls.
!section 03.03.01 types vs. subtypes; strong typing
!section 03.03.01 Using base type name in type definition
!section 03.05.01 'FIRST of enumeration literal has position number zero
!section 03.05.05 'RANGE and 'LENGTH not defined for scalar types
!section 03.05.05 VAL attribute depends on rep. clause
!section 03.05.09 Failure to include range in fixed point declaration
!section 03.05.09 Fixed point subtype declarations
!section 03.06    No partially constrained arrays
!section 03.06.02 no numeric operators for array types
!section 03.07    No anonymous array types for record components
!section 03.08.01 Using an incomplete type prematurely
!section 04.01.03 Using Pointers and .all
!section 04.01.03 Using .all to access whole records
!section 04.03.02 Rules for others choice in array aggregate
!section 04.03.02 Rules for using others choice
!section 04.04    Can't parenthesize range
!section 04.05.04 precedence of unary minus
!section 06.02    Slices used as actual parameters
!section 06.03    ; instead of IS in subprogram bodies
!section 08.03    visibility rules for operators
!section 08.03    visibility of operators
!section 08.05    renaming task entries
!section 08.05    ignoring constraints in renaming
!section 09.04    Nested task termination and leaving block
!section 09.06    delay 2.5*minutes is illegal
!section 09.07.01 evaluation of guards
!section 10.01.01 A with clause is not like an Include
!section 10.01.01 confusion of with and use
!section 10.02    Spelling SEPARATE correctly
!section 11.04.02 Handling exceptions raised in declarations
!section 12.01    No out mode for generic formal objects
!section 12.01    no overloaded generic units
!section 14.03    I/O calls in tasks

!section 00.00                                                       ER-00005
!topic different uses of =>
!background Basic
!experience none

The students with very little programming experience (usually only Basic)
also report an interesting problem.  They cannot seem to get the meaning
of the compound delemeter arrow (=>) because it is used in so many places...

	case x is
	   when 1 => ...

	exception
	   when Constraint_Error => ...

	A : array (1 .. 10) of integer;
	begin
		A := (1 .. 3 => 2, 5 ! 7 => 3, others => 8);

	text_io.put (file => f, item => "hi john... are you at wang now?");

*****************

!section 00.00                                                       ER-00007
!topic variables set but not referenced, and vice versa

Here's my candidate for the most common Ada bug that compilers
don't have to check for:  Variables that are set but not referenced,
or referenced but not set.  Checking this along all possible paths
is equivalent to the halting problem, but the simple case is
equivalent to checking that functions have return statements somewhere
in them, and would catch a very large number of bugs.

*****************

!section 02.03      02.04                                            ER-00023
!topic illegal use of underscore

Invalid Identifiers and Numeric Literals:

  A__B, A_, _A, 3_, 3__0, 3_.0, 3._0, etc.

*****************

!section 02.05      02.06                                            ER-00026
!topic one character string literals or character literals

procedure P is
  C : Character := 'z';
  S : String(1..1);
begin
  S := C;
  C := S;
  C := "z";
  S := 'z';
end P;

Incompatible types problem (easily corrected though). Incorrect use of
quotation characters (easily corrected).

*****************

!section 02.09                                                       ER-00018
!topic inadvertant use of reserved words

type Greek_Letters is (Alpha, Beta, Gamma, Delta, Epsilon);
type Direction is (Forward, Reverse, Up, Down);
type Digits is range 0 .. 9;

Thou shalt not use the reserved words in vain.

*****************

!section 03.02                                                       ER-00024
!topic anonymous array types

A1, A2 : array(1 .. 10) of Boolean;
 . . .
A1 := A2;

The old anonymous array type problem.

*****************

!section 03.02.02                                                    ER-00020
!topic Using non-universal constants in number decls.

Var1 : constant Integer := 3;
Var2 : constant Integer := 4;
Var3 : constant := Var1 + Var2;

One cannot convert from a named type to a universal type (its a one-way
street only).
[Actually, can use Integer'Pos(Var1) + Integer'Pos(Var2). JBG]

*****************

!section 03.03.01                                                    ER-00004
!topic types vs. subtypes; strong typing
!background Fortran
!experience students

the most common problem my students tell me about has to do with
the difference between base types and subtypes.  For example...

function factorial (of_n : natural) return natural;

type numbers is range 1 .. 10;
n : numbers := 3;
f : natural;
begin
	f := factorial (n);

This will not compile.  They seem to think that all integer types should
be subtypes of Integer and Integer should contain all possible integer
values for a specific implementation.  It is the people with Fortran
backgrounds who really have trouble with this and strong typing in
general.

*****************

!section 03.03.01                                                    ER-00016
!topic Using base type name in type definition

type I is Integer range 1 .. 10;

One cannot create a base type using another base type. Typically three
solutions to this problem are:

  type I is range 1 .. 10;
  type I is new Integer range 1 .. 10;
  subtype I is Integer range 1 ..10;

*****************

!section 03.05.01                                                    ER-00030
!topic 'FIRST of enumeration literal has position number zero

some_enumeration_type'POS(same_enumeration_type'FIRST) = 0  ???

Many programmers believe that this expression equals 1, most
notably for CHARACTER'POS(CHARACTER'FIRST). This causes many
tricky algorithmic problems which take a novice a long time to
debug.

*****************

!section 03.05.05                                                    ER-00009
!topic 'RANGE and 'LENGTH not defined for scalar types

It seems inconsistent that the attributes 'first, 'last, 'range,
and 'length apply to arrays, but only 'first and 'last also apply
to scalars.

*****************

!section 03.05.05                                                    ER-00031
!topic VAL attribute depends on rep. clause

The VAL attribute does not work in logical terms. In the presence
of a rep. spec., the VAL attribute will return the value
specified in that rep. spec. (assuming rep specs are
implemented). Note that the Barnes text has this wrong (page
266).

*****************

!section 03.05.09                                                    ER-00036
!topic Failure to include range in fixed point declaration

type My_Fixed is delta 0.01;

A base type of  a fixed point type must state an explicit
range. Note that floating point base types need not state a
range.

*****************

!section 03.05.09                                                    ER-00037
!topic Fixed point subtype declarations

type My_Fixed is delta 0.1 range 1.0 .. 2.0;
subtype Sub_Fixed is My_Fixed delta 0.01 range 0.0 .. 3.0;

type My_Float is digits 2 range 1.0 .. 2.0;
subtype Sub_Float is My_Float digits 3 range 0.0 .. 3.0;

The subtypes will cause CONSTRAINT_ERROR to be raised since they
each specify a greater accuracy and range of values than their
respective base types.

*****************

!section 03.06                                                       ER-00033
!topic No partially constrained arrays

type A is array(BOOLEAN, INTEGER range <>) of CHARACTER;

One cannot define an array type which has constrained and
unconstrained indices mixed.

*****************

!section 03.06.02                                                    ER-00010
!topic no numeric operators for array types

It seems inconsistent that the operators NOT, AND, OR, and XOR
are implicitly defined on any boolean type or array of boolean types,
but the implicit operators for numeric types are not defined for
arrays of numeric types.

*****************

!section 03.07                                                       ER-00025
!topic No anonymous array types for record components

type R is record
  . . .
  Arr : array(1 .. 10) of Boolean;
end R;

No anonymous array types allowed in a record type.

*****************

!section 03.08.01                                                    ER-00021
!topic Using an incomplete type prematurely

type Link;
type Node is
  record
    . . .
    Next : Link;
  end record;
type Link is access Node;

The incomplete type declaration should be used for Node, not Link.

*****************

!section 04.0.03                                                     ER-00040
!topic Using Pointers and .all

Also, some programmers still haven't got the difference down
between the following two if-then conditions:

  type Access_R is access R;
  A1, A2 : Access_R := . . .;

  if A1 = A2 then . . . end if;
            vs.
  if A1.all = A2.all then . . . end if;

*****************

!section 04.01.03                                                    ER-00039
!topic Using .all to access whole records

type R is
  record
    . . .
  end record;
. . .
R1, R2 : R;
. . .
if R1.all = R2.all then . . . end if;

The ".all" suffix applies only to access values. When dealing
with record objects, simply stating the object without a selected
component is equivalent to a ".all" semantics for access values.

*****************

!section 04.03.02                                                    ER-00014
!topic Rules for others choice in array aggregate

Paragraph (4) of 4.3.2 states:

	"An others choice is only allowed if the aggregate appears in
one of the following contexts ..."

	I tried to give a default initialization to a
record component which was an array.  It didn't work, so I had to
provide a record assignment.  Instead of:

	type Attribute_Type is ( .. enumeration class .. );
	type Listing_Type   is ( .. enumeration class .. );

	type Display_Option is array( Attribute_Type ) of BOOLEAN;
	type Display_Record is 
	  record
	    LISTING : Listing_Type   := LIST_BY_NAME;
	    CHOICES : Display_Option := (others => TRUE );
	  end record;
	CURRENT : Display_Record;

I had to:

	type Display_Record is 
	  record
	    LISTING : Listing_Type;
	    CHOICES : Display_Option;
	  end record;
	CURRENT : Display_Record := (LIST_BY_NAME, (others=>TRUE) );

This seems to be a rather arbitrary (non-mnemonic = error-prone) rule of
the language.

	Another trivial point: for STRINGS (arrays of CHARACTER), notice
the difference of use:

	A_SMALL_STRING : STRING(1..1) := (others => ' ');
 begin
	A_SMALL_STRING := " ";

*****************

!section 04.03.02                                                    ER-00038
!topic Rules for using others choice

type My_Array is array(INTEGER range 1 .. 10) of BOOLEAN;
. . .
A : My_Array := (1 .. 3 => FALSE, others => TRUE);

Cannot use an others clause in the presence of named notation
where one or more choices represents a range of values. The
tricky rules on the use of an others clause play havic with Ada
programmers. Some even get so frustrated as to how/where an
others clause can appear that they simply never try to use it.
The rules should be made clear to these programmers (described at
their own level -- they cannot understand the language of the
ARM).

*****************

!section 04.04                                                       ER-00015
!topic Can't parenthesize range
!background broad

C : Character;
 . . .
if C in ('A' .. 'Z') then . . . end if;

One cannot parenthesize the range for a membership test.

*****************

!section 04.05.04                                                    ER-00008
!topic precedence of unary minus

The low precedence of unary minus would surprise those with a
math background,  I would think.  -11 mod 5 is interpreted as
-(11 mod 5) which is -1.  The other interpretation (-11) mod 5
equals 4.

*****************

!section 06.02                                                       ER-00006
!topic Slices used as actual parameters

function string_eq(left, right: string) return boolean is
--returns true iff the two string parameters have the same value.
begin
   if left'length /= right'length then return false; end if;
   for i in left'range loop
      if left(i) /= right(i) then return false; end if;
   end loop;
   return true;
end string_eq;

   The bug in this code is insidious because the routine works fine
in most cases.  It fails though when the right parameter is a slice
such that right'first /= left'first.  I think the principle of least
surprise would dictate that slice parameters be normalized similar
to how they are in slice assignment, although the unconstrained case
doesn't apply for assignment.  This bug could easily bite anyone
not sufficiently immunized from previous bites.

*****************

!section 06.03                                                       ER-00001
!topic ; instead of IS in subprogram bodies
!background Pascal
!experience students

Error: using ";" instead of "IS" after procedure headers, especially
	on the heading of a file.
Reason for error: mostly a carry-over from Pascal and Modula-2.
Source of error: personal experience learning Ada.
Occurance: most likely by programmers still learning Ada.
Reason this is a problem: large number of fall-out error messages
	as the compiler then mis-interprets the entire block 
	structure of the file.  The actual error is not even flagged.

*****************

!section 08.03                                                       ER-00013
!topic visibility rules for operators

I find that scoping rules for user defined types is an error prone "concept"
(as opposed to construct).  As you pointed out to me once before* according
to 8.3(18) an "operator is directly visible if and only if the corresponding
operator declaration is directly visible."  Yet, it is natural to write
something like the following (especially for 1st time users):

	package pack1 is
	  type int is range 1..1000;
	end pack1;

	with pack1;
	procedure demo is
	  i: pack1.int := 5;
	begin
	  .
	  i := i+1;			-- illegal
	  .
	  .
	end demo;

I realize that I could use a USE clause or RENAME the "+" operation, but I
feel that not using the full name in most situtations is less readable and
that both the USE clause & RENAMING are error prone (in fact 1 project here
has totally disallowed both) .  I would like to set up a project standard
where USE clause is only used for command package that are deemed acceptable
by project management (e.g., predefined packages and project global
definitions).  However, if I adopt such a standard I loose any benifit from
defining operators and in cases such as the one above I cannot use infixed
notation even for predefined operators, unless pack1 is one of my
"acceptable" packages.  On the other hand, If I allow the use of USE, but
require that full names be used (except maybe in specific situations), than
I can no longer use the compiler to enforce the full name requirement.

Unfortunately, I don't see a clean solution to this problem since redefine
the scope of an operator to be extended to the scope of the type(s) that it
operates on (for example) would be extremely difficult to define proprely
for operators that have parameters of different types.

*****************

!section 08.03                                                       ER-00022
!topic visibility of operators

package P is
  type T is (T1, T2);
end P;
with P;
procedure Main is
  V1, V2 : P.T;
begin
  . . .
  if V1 = V2 then . . . end if;
end Main;

One must explicitly import operations from another scope. Best solution is
to use a renames in the declarative region of Main:

  function "="(L, R : in P.T) return Boolean renames P."=";

One could also use a "use clause", expanded notation on P."=", or the Pos
attribute to convert V1 and V2 to universal_integers so that they could be
compared for equality. All of these solutions are less than desirable.

*****************

!section 08.05                                                       ER-00017
!topic renaming task entries

On trying to "hide" tasks in a package body:

package P is
  procedure I_Am_Trying_to_be_a_Task_Entry;
end P;
package body P is
  task T is
    entry E;
  end T;
  task body T is
  begin
    accept E;
  end;
  procedure I_Am_Trying_to_be_a_Task_Entry renames T.E;
end P;

One solution to this problem (albeit not the best one) is:

  package P is . . . end P;
  package body P is
    . . .
    procedure I_Am_Trying_to_be_a_Task_Entry is
    begin
      T.E;
    end;
  end P;

*****************

!section 08.05                                                       ER-00027
!topic ignoring constraints in renaming

procedure P is
  A : Integer;
  B : Positive renames A;
  C : Positive;
  D : Integer renames C;
begin
  B := -10;
  D := B;
end P;

Obviously, the user doesn't understand that constraints implied by a type
mark on a renaming are ignored and the constraints are that of the actual.
Constraint_Error will be raised during the attempt to assign B to D.

*****************

!section 09.04                                                       ER-00034
!topic Nested task termination and leaving block

procedure Main is
  task T is
    entry E(. . .);
  end T;
  task body T is
  begin
    loop
      accept E(. . .) do ... end E;
    end loop;
  end T;
begin
  while <condition> loop
    . . .
    T.E(. . .);
     . . .
  end loop;
end Main;

Many programmers don't realize that task T causes termination
problems. The accept statement in task T can be replaced by the
following select statement to provide the desired semantics and
thus eliminate the termination problems:

  select
    accept E(. . .) do . . . end E;
  or
    terminate;
  end select;

*****************

!section 09.06                                                       ER-00019
!topic delay 2.5*minutes is illegal

Minutes : constant DURATION := 60.0;
 . . .
delay 2.5 * Minutes;

This is the old "result is universal_fixed" problem. Two solutions are:

  -- make "Minutes" an Integer type equal to 60
  -- used explicit type conversion on the result of the delay expression

*****************

!section 09.07.01                                                    ER-00003
!topic evaluation of guards

I think the area which seem to be the most error prone in Ada is the
processing of guards in conditional selects.  Both Ichbiah and Barnes
have published programs that will not work because they assumed the
guards and the entry calls are atomic or tasks don't abort.

*****************

!section 10.01.01                                                    ER-00002
!topic A with clause is not like an Include
!background Pascal
!experience students

with text_io; use text_io;
package int_io is new integer_io(integer);
with int_io; use int_io;
with text_io; use text_io; -- this line  gets forgotten because "I defined
                           -- it once!"
procedure foo is
  answer: constant integer := 42;
  begin
   put (answer);
   put_line (" is the answer");
  end;

This has been made by Pascal programmers who think of the with facility
as an include whose scope is the entire source file.

*****************

!section 10.01.01                                                    ER-00012
!topic confusion of with and use
!background Pascal

Pascal programmers confuse the effects of with and use clause

*****************

!section 10.02                                                       ER-00011
!topic Spelling SEPARATE correctly

Programmers have complained about not remembering how
to spell 'separate'.

*****************

!section 11.04.02                                                    ER-00035
!topic Handling exceptions raised in declarations

procedure Main
  I : POSITIVE := 0;
begin
  . . .
exception
  when CONSTRAINT_ERROR => -- for I's declaration
    . . .
end Main;

The exception handler won't catch CONSTRAINT_ERROR for the
elaboration of I. Exception handlers do not catch exceptions
originating from a declarative region outside of their scope.

*****************

!section 12.01                                                       ER-00029
!topic No out mode for generic formal objects

generic
  I : out INTEGER;
package P is ... end P;

Cannot have a mode "out" generic formal object.

*****************

!section 12.01                                                       ER-00032
!topic no overloaded generic units

package P is
  generic
    with function F return INTEGER;
  procedure P(X : INTEGER);
  . . .
  generic
    with function F return INTEGER;
  procedure P(Y : FLOAT);
  . . .
end P;

Many programmers thought that the two generics could be
overloaded properly since they thought they could be
distinguished by procedure P's formal parameter list. Of course,
this is not true, and the two generic are homographs.

*****************

!section 14.03                                                       ER-00028
!topic I/O calls in tasks

The part of Ada that continuously gives me and others a hard
time is text_io. Last Friday 3 of us wasted an hour until
we concluded that text_io is a single thread package and
cannot support simultaneous calls to get and put (one in each
of two tasks). In the recent past I have had difficulty
with while loops which look for EOF and doing a get in
the loop.

*****************

goodenou@wanginst.UUCP (John Goodenough) (01/28/86)

Last Fall, I asked people to send me examples of errors they make (or have
seen made) when writing Ada programs.  I received a modest response which I
have recently augmented by perusing some vendor problem report files to find
those reports where the compiler turned out to be right.  The review of vendor
problem reports has about doubled the number of error examples to 70-80.  

I'm still collecting errors.  Send in your contribution by net mail or snail
mail (even handwritten is okay).  Maybe you could send a memo to some of your
colleagues asking them to jot down one or two Ada programming errors that
stick in their mind, and send me the raw data.

I have found that Ada-related programming errors can be usefully classified as
follows:

        .  PERCEIVED NON-UNIFORMITIES in the language: exceptions to
           rules that are in the minds of programmers, e.g.,
    
                .  the precedence of unary minus is different from the
                   precedence of other unary operators (although the same
                   as the precedence of binary minus)

        .  NEW CONCEPTS: differences from previously used programming
           languages that cause confusion, e.g.,

                .  each type declaration declares a distinct type

        .  UNAVOIDABLE COMPLEXITIES: complex rules that trip up the
           everyday programmer, e.g.,

                .  rules for use of OTHERS in array aggregates

        .  BLUNDERS: mistakes that are easy to make even though the
           rules are clear, e.g., 

                .  inadvertent use of reserved words as in

                   type Direction is (Forward, Reverse, Up, Down, Left, Right);

        .  UNEXPECTED EFFECTS: unappreciated consequences of rules,
           leading to subtle bugs in programs, e.g.,

                .  effect of attempting to read the sequence 

                        13 16.2 

                   with GET instantiated for type INTEGER.

(This last category contains some of the most interesting errors.)

A document containing the errors using this classification scheme will be
prepared in a few months.  In the meantime, I'm including in this message the
topic lines for the errors currently in the collection.  If you want to see the
full set of errors right away (about 42K characters), send me a net message.

			    Ada Programmer Errors

        0.0       different uses of =>
        0.0       variables set but not referenced, and vice versa
        2.3       illegal use of underscore
        2.5       one character string literals or character literals
        2.9       inadvertent use of reserved words
        3.2       anonymous array types
        3.2.2     Using non-universal constants in number decls.
        3.3.1     types vs. subtypes; strong typing
        3.3.1     Using base type name in type definition
        3.3.1(4)  type declarations declare distinct types
        3.5.1     'FIRST of enumeration literal has position number zero
        3.5.5     'RANGE and 'LENGTH not defined for scalar types
        3.5.5     VAL attribute does not depend on rep. clause
        3.5.9     Failure to include range in fixed point declaration
        3.5.9     Fixed point subtype declarations
        3.6       No partially constrained arrays
        3.6.2     no numeric operators for array types
        3.6.3     Length of actual string parameter arguments
        3.6.3(1)  the index subtype for STRING is Integer
        3.7       No anonymous array types for record components
        3.7.1     NUMERIC_ERROR for unconstrained record objects
        3.8.1     Using an incomplete type prematurely
        3.9(2)    basic declarations not allowed after bodies
        3.9(6)    Activating a task whose body has not been elaborated
        4.0.3     Using Pointers and .all
        4.1.3     Using .all to access whole records
        4.3(4)    aggregates with only one component
        4.3.2     Rules for using others choice
        4.4       Can't parenthesize range
        4.5.4     precedence of unary minus
        4.9(8)    Size of a record is not static
        5.2       Failure to use aggregates in assignments
        5.2.1(2)  No sliding of array components in record aggregates
        5.4(2)    not all choices can be parenthesized
        5.4(4)    Use of RANGE attribute in loops and case statements
        6.2       Slices used as actual parameters
        6.2(2)    Incorrect use of formal parameter modes
        6.2(5)    Assignment to component designated by OUT parameter
        6.3       ; instead of IS in subprogram bodies
        6.3(2)    Bodies that use IS rather than semicolon
        6.3.1(5)  can't omit IN in parameter decl if it is present in body
        6.3.2(4)  dependence on body due to INLINE
        6.6(1)    Parameter names not considered in overloaded declarations
        8.3       visibility rules for operators
        8.3       visibility of operators
        8.3(15)   Object declaration hides outer procedure declaration
        8.3(18)   Need a use clause to get visibility of operators
        8.4(5)    Conflict with a name declared in Standard
        8.4(6)    Effect of USE on generic subprograms
        8.4(6)    Use clause and renamed exceptions
        8.5       renaming task entries
        8.5       ignoring constraints in renaming
        9.4       Nested task termination and leaving block
        9.4(13)   Termination of library tasks
        9.6       delay 2.5*minutes is illegal
        9.6(1)    Delay statments can be used in the main program
        9.7.1     evaluation of guards
        10.1(6)   recompiling a library subprogram body
        10.1.1    A with clause is not like an Include
        10.1.1    confusion of with and use
        10.2      Spelling SEPARATE correctly
        10.2(5)   Overloaded subunits are illegal
        10.2(5)   Subunits cannot be operators
        10.5(3)   Failure to use pragma ELABORATE for generic units
        11.4.2    Handling exceptions raised in declarations
        12.1      No out mode for generic formal objects
        12.1      no overloaded generic units
        14.3      I/O calls in tasks
        14.3      Associating two file variables with a terminal
        14.3.5(3) PUT at the end of the program
        14.3.7(6) Use of Integer GET to read real literals
        14.3.9(6) Failing to advance after DATA_ERROR for GET

John B. Goodenough                           goodenou@wanginst        (CSNET)
Wang Institute of Graduate Studies           decvax!wanginst!goodenou (UUCP)
Tyng Road, Tyngsboro, MA 01879               Goodenough@ISI           (ARPA)
(At Wang Institute until 6/1/86)             617-649-9731