Sun Studio 12: Fortran Programming Guide

7.6.2 Aliasing and the -xalias Option

Aliasing occurs when the same storage address is referenced by more than one name. This typically happens with pointers, or when actual arguments to a subprogram overlap between themselves or between COMMON variables within the subprogram. For example, arguments X and Z refer to the same storage locations, as do B and H:


  COMMON /INS/B(100)
  REAL S(100), T(100)
  ...
  CALL SUB(S,T,S,B,100)
  ...
  SUBROUTINE SUB(X,Y,Z,H,N)
  REAL X(N),Y(N),Z(N),H(N)
  COMMON /INS/B(100)
  ...

Many “dusty deck” Fortran programs utilized this sort of aliasing as a way of providing some kind of dynamic memory management that was not available in the language at that time.

Avoid aliasing in all portable code. The results could be unpredictable on some platforms and when compiled with optimization levels higher than -O2.

The f95 compiler assumes it is compiling a standard-conforming program. Programs that do not conform strictly to the Fortran standard can introduce ambiguous situations that interfere with the compiler’s analysis and optimization strategies. Some situations can produce erroneous results.

For example, overindexing arrays, use of pointers, or passing global variables as subprogram arguments when also used directly, can result in ambiguous situations that limit the compiler’s ability to generate optimal code that will be correct in all situations.

If you know that your program does contain some apparent aliasing situations you can use the -xalias option to specify the degree to which the compiler should be concerned. In some cases the program will not execute properly when compiled at optimization levels higher than -O2 unless the appropriate -xalias option is specified.

The option flag takes a comma-separated list of keywords that indicate a type of aliasing situation. Each keyword can be prefixed by no% to indicate an aliasing that is not present.

Table 7–2 -xalias Keywords and What They Mean

-xalias= keyword

Aliasing situation  

dummy

Dummy subprogram arguments can alias each other and global variables. 

no%dummy

The Fortran standard is followed and dummy arguments do not alias each other or global variables in the actual call. (This is the default.) 

craypointer

The program uses Cray pointers that can point anywhere. (This is the default.) 

no%craypointer

Cray pointers always point at distinct memory areas, or are not used. 

ftnpointer

Any Fortran 95 pointer can point to any target variable, regardless of type, kind, or rank. 

no%ftnpointer

Fortran 95 pointers follow the rules of the standard. (This is the default.) 

overindex

There are four overindexing situations that can be caused by violating the subscript bounds in an array reference, and any one or more of these may appear in the program: 

  • A reference to an element of an array in a COMMON block could refer to any element in a COMMON block or equivalence group.

  • Passing an element of a COMMON block or equivalence group as an actual argument to a subprogram gives access to any element of that COMMON block or equivalence group.

  • Variables of a sequence derived type are treated as if they were COMMON blocks, and elements of a such a variable may alias other elements of that variable.

  • Individual array subscript bounds may be violated, even though the array reference stays within the array.

    overindex does not apply to array syntax, WHERE, and FORALL statements. If overindexing occurs in these constructs, they should be rewritten as DO loops.

no%overindex

Array bounds are not violated. Array references do not reference other variables. (This is the default.) 

actual

The compiler treats actual subprogram arguments as if they were global variables. Passing an argument to a subprogram may result in aliasing through Cray pointers. 

no%actual

Passing an argument to a subprogram does not cause further aliasing. (This is the default.) 

Here some examples of typical aliasing situations. At the higher optimization levels (-O3 and above) the f95 compiler can generate better code if your program does not contain the aliasing syndromes shown below and you compile with -xalias=no%keyword.

In some cases you will need to compile with -xalias=keyword to insure that the code generate will produce the correct results.

7.6.2.1 Aliasing Through Dummy Arguments and Global Variables

The following example needs to be compiled with -xalias=dummy


parameter (n=100)
integer a(n)
common /qq/z(n)
call sub(a,a,z,n)
...
subroutine sub(a,b,c,n)
integer a(n), b(n)
common /qq/z(n)
a(2:n) = b(1:n-1)
c(2:n) = z(1:n-1)
The compiler must assume that the dummy variables and the common variable may overlap.

7.6.2.2 Aliasing Introduced With Cray Pointers

This example works only when compiled with -xalias=craypointer, which is the default:


parameter (n=20)
integer a(n)
integer v1(*), v2(*)
pointer (p1,v1)
pointer (p2,v2)
p1 = loc(a)
p2 = loc(a)
a = (/ (i,i=1,n) /)
...
v1(2:n) = v2(1:n-1)
The compiler must assume that these locations can overlap.

Here is an example of Cray pointers that do not overlap. In this case, compile with -xalias=no%craypointer for possibly better performance:


parameter (n=10)
integer a(n+n)
integer v1(n), v2(n)
pointer (p1,v1)
pointer (p2,v2)
p1 = loc(a(1))
p2 = loc(a(n+1))
...
v1(:) = v2(:)
The Cray pointers to not point to overlapping memory areas.

7.6.2.3 Aliasing Introduced With Fortran 95 Pointers

Compile the following example with -xalias=ftnpointer


parameter (n=20)
integer, pointer :: a(:)
integer, target :: t(n)
interface
  subroutine sub(a,b,n)
    integer, pointer :: a(:)
    integer, pointer :: b(:)
  end subroutine
end interface

a => t
a = (/ (i, i=1,n) /)
call sub(a,a,n)
....
end
subroutine sub(a,b,n)
 integer, pointer :: a(:)
 real, pointer :: b(:)
 integer i, mold

 forall (i=2:n)
   a(i) = transfer(b(i-1), mold)
The compiler must assume that a and b can overlap.

Note that in this example the compiler must assume that a and b may overlap, even though they point to data of different data types. This is illegal in standard Fortran. The compiler gives a warning if it can detect this situation.

7.6.2.4 Aliasing By Overindexing

Compile the following example with -xalias=overindex


integer a,z
common // a(100),z
z = 1
call sub(a)
print*, z
subroutine sub(x)
  integer x(10)
  x(101) = 2
The compiler may assume that the call to sub may write to z
The program prints 2, and not 1, when compiled with -xalias=overindex

Overindexing appears in many legacy Fortran 77 programs and should be avoided. In many cases the result will be unpredictable. To insure correctness, programs should be compiled and tested with the -C (runtime array bounds checking) option to flag any array subscripting problems.

In general, the overindex flag should only be used with legacy Fortran 77 programs. -xalias=overindex does not apply to array syntax expressions, array sections, WHERE, and FORALL statements.

Fortran 95 programs should always conform to the subscripting rules in the Fortran standard to insure correctness of the generated code. For example, the following example uses ambiguous subscripting in an array syntax expression that will always produce an incorrect result due to the overindexing of the array:


This example of array syntax overindexing DOES NOT GIVE CORRECT RESULTS!

   parameter (n=10)
   integer a(n),b(n)
   common /qq/a,b
   integer c(n)
   integer m, k
   a = (/ (i,i=1,n) /)
   b = a
   c(1) = 1
   c(2:n) = (/ (i,i=1,n-1) /)

   m = n
   k = n + n
C
C   the reference to a is actually a reference into b
C   so this should really be  b(2:n) = b(1:n-1)
C
   a(m+2:k) = b(1:n-1)

C  or doing it in reverse
   a(k:m+2:-1) = b(n-1:1:-1)

Intuitively the user might expect array b to now look like array c, but the result is unpredictable

The xalias=overindex flag will not help in this situation since the overindex flag does not extend to array syntax expressions. The example compiles, but will not give the correct results. Rewriting this example by replacing the array syntax with the equivalent DO loop will work when compiled with -xalias=overindex. But this kind of programming practice should be avoided entirely.

7.6.2.5 Aliasing By Actual Arguments

The compiler looks ahead to see how local variables are used and then makes assumptions about variables that will not change over a subprogram call. In the following example, pointers used in the subprogram defeat the compiler’s optimization strategy and the results are unpredictable. To make this work properly you need to compile with the -xalias=actual flag:


 program foo
      integer i
      call take_loc(i)
      i = 1
      print * , i
      call use_loc()
      print * , i
   end

   subroutine take_loc(i)
      integer i
      common /loc_comm/ loc_i
      loc_i = loc(i)
   end subroutine take_loc

   subroutine use_loc()
      integer vi1
      pointer (pi,vi)
      common /loc_comm/ loc_i
      pi = loc_i
      vi1 = 3
   end subroutine use_loc

take_loc takes the address of i and saves it away. use_loc uses it. This is a violation of the Fortran standard.

Compiling with the -xalias=actual flag informs the compiler that all arguments to subprograms should be considered global within the compilation unit, causing the compiler to be more cautious with its assumptions about variables appearing as actual arguments.

Programming practices like this that violate the Fortran standard should be avoided.

7.6.2.6 -xalias Defaults

Specifying -xalias without a list assumes that your program does not violate the Fortran aliasing rules. It is equivalent to asserting no% for all the aliasing keywords.

The compiler default, when compiling without specifying -xalias, is:

-xalias=no%dummy,craypointer,no%actual,no%overindex,no%ftnpointer

If your program uses Cray pointers but conforms to the Fortran aliasing rules whereby the pointer references cannot result in aliasing, even in ambiguous situations, compiling with -xalias may result in generating better optimized code.