Go to main content
Oracle® Developer Studio 12.5: Fortran User's Guide

Exit Print View

Updated: June 2016
 
 

2.3 Directives

Use a source code directive, a form of Fortran comment, to pass specific information to the compiler regarding special optimization or parallelization choices. Compiler directives are also sometimes called pragmas. The compiler recognizes a set of general directives and parallelization directives, including OpenMP directives.

Directives unique to f95 are described in Directives. A complete summary of all the directives recognized by f95 appears in Fortran Directives Summary.


Note - Directives are not part of the Fortran standard.

2.3.1 General Directives

The various forms of a general Fortran directive are:

!$PRAGMA keyword ( a [ , a ] ) [ , keyword ( a [ , a ] ) ] ,

!$PRAGMA SUN keyword ( a [ , a ] … ) [ , keyword ( a [ , a ] … ) ] ,…

The variable keyword identifies the specific directive. Additional arguments or suboptions may also be allowed. (Some directives require the additional keyword SUN, as shown above.)

A general directive has the following syntax:

  • In column one, any of the comment-indicator characters c, C, !, or *

  • For f95 free-format, ! is the only comment-indicator recognized (!$PRAGMA). The examples in this chapter assume Fortran 95 free-format.

  • The next seven characters are $PRAGMA, no blanks, in either uppercase or lowercase.

  • Directives using the ! comment-indicator character may appear in any position on the line for free-format source programs.

Observe the following restrictions:

  • After the first eight characters, blanks are ignored, and uppercase and lowercase are equivalent, as in Fortran text.

  • Because it is a comment, a directive cannot be continued, but you can have many !$PRAGMA lines, one after the other, as needed.

  • If a comment satisfies the above syntax, it is expected to contain one or more directives recognized by the compiler; if it does not, a warning is issued.

  • The C preprocessor, cpp, will expand macro symbol definitions within a comment or directive line; the Fortran preprocessor, fpp, will not expand macros in comment lines. fpp will recognize legitimate f95 directives and allow limited substitution outside directive keywords. However, be careful with directives requiring the keyword SUN. cpp will replace lower-case sun with a predefined value. Also, if you define a cpp macro SUN, it might interfere with the SUN directive keyword. A general rule would be to spell those pragmas in mixed case if the source will be processed by cpp or fpp, as in:

    !$PRAGMA Sun UNROLL=3.

    Another workaround might be to add -Usun when compiling a .F file.

The Fortran compiler recognizes the following general directives:

Table 2  Summary of General Fortran Directives
C Directive
!$PRAGMA C(list)
Declares a list of names of external functions as C language routines.
IGNORE_TKR Directive
!$PRAGMA IGNORE_TKR {name {, name} ...}
The compiler ignores the type, kind, and rank of the specified dummy argument names appearing in a generic procedure interface when resolving a specific call.
UNROLL Directive
!$PRAGMA SUN UNROLL=n
Advises the compiler that the following loop can be unrolled to a length n.
WEAK Directive
!$PRAGMA WEAK(name[=name2])
Declares name to be a weak symbol, or an alias for name2.
OPT Directive
!$PRAGMA SUN OPT=n
Set optimization level for a subprogram to n.
PIPELOOP Directive
!$PRAGMA SUN PIPELOOP=n
Assert dependency in the following loop exists between iterations n apart.
PREFETCH Directives
!$PRAGMA SUN_PREFETCH_READ_ONCE(name)
!$PRAGMA SUN_PREFETCH_READ_MANY(name)
!$PRAGMA SUN_PREFETCH_WRITE_ONCE(name)
!$PRAGMA SUN_PREFETCH_WRITE_MANY(name)
Request compiler generate prefetch instructions for references to name. (Requires -xprefetch option, which is enabled by default. Prefetch directives can be disabled by compiling with —xprefetch=no. Target architecture must also support prefetch instructions, and the compiler optimization level must be greater than —xO2.)
ASSUME Directives
!$PRAGMA [BEGIN} ASSUME (expression [,probability])
!$PRAGMA END ASSUME
Make assertions about conditions at certain points in the program that the compiler can assume are true.

2.3.1.1 The C Directive

The C() directive specifies that its arguments are external functions. It is equivalent to an EXTERNAL declaration except that unlike ordinary external names, the Fortran compiler will not append an underscore to these argument names.

The C() directive for a particular function should appear before the first reference to that function in each subprogram that contains such a reference.

Example - compiling ABC and XYZ for C:

       EXTERNAL ABC, XYZ
!$PRAGMA C(ABC, XYZ)

2.3.1.2 The IGNORE_TKR Directive

This directive causes the compiler to ignore the type, kind, and rank of the specified dummy argument names appearing in a generic procedure interface when resolving a specific call.

For example, in the procedure interface below, the directive specifies that SRC can be any data type, but LEN can be either KIND=4 or KIND=8.The interface block defines two specific procedures for a generic procedure name.This example is shown in Fortran 95 free format.

INTERFACE BLCKX

SUBROUTINE BLCK_32(LEN,SRC)
  REAL SRC(1)
!$PRAGMA IGNORE_TKR SRC
  INTEGER (KIND=4) LEN
END SUBROUTINE

SUBROUTINE BLCK_64(LEN,SRC)
  REAL SRC(1)
!$PRAGMA IGNORE_TKR SRC
  INTEGER (KIND=8) LEN
END SUBROUTINE

END INTERFACE

The subroutine call:

INTEGER L
REAL S(100)
CALL BLCKX(L,S)

The call to BLCKX will call BLCK_32 when compiled normally, and BLCK_64 when compiled with -xtypemap=integer:64. The actual type of S does not determine which routine to call. This greatly simplifies writing generic interfaces for wrappers that call specific library routines based on argument type, kind, or rank.

Note that dummy arguments for assumed-shape arrays, Fortran pointers, or allocatable arrays cannot be specified on the directive. If no names are specified, the directive applies to all dummy arguments to the procedure, except dummy arguments that are assumed-shape arrays, Fortran pointers, or allocatable arrays.

2.3.1.3 The UNROLL Directive

The UNROLL directive requires that you specify SUN after !$PRAGMA.

The !$PRAGMA SUN UNROLL=n directive instructs the compiler to unroll the following loop n times during its optimization pass. (The compiler will unroll a loop only when its analysis regards such unrolling as appropriate.)

n is a positive integer. The choices are:

  • If n=1, the optimizer may not unroll any loops.

  • If n>1, the optimizer may unroll loops n times.

If any loops are actually unrolled, the executable file becomes larger.

Example - unrolling loops two times:

!$PRAGMA SUN UNROLL=2

2.3.1.4 The WEAK Directive

The WEAK directive defines a symbol to have less precedence than an earlier definition of the same symbol. This pragma is used mainly in sources files for building libraries. The linker does not produce an error message if it is unable to resolve a weak symbol.

!$PRAGMA WEAK (name1 [=name2])

WEAK (name1) defines name1 to be a weak symbol. The linker does not produce an error message if it does not find a definition for name1.

WEAK (name1=name2) defines name1 to be a weak symbol and an alias for name2.

If your program calls but does not define name1, the linker uses the definition from the library. However, if your program defines its own version of name1, then the program’s definition is used and the weak global definition of name1 in the library is not used. If the program directly calls name2, the definition from library is used; a duplicate definition of name2 causes an error. See the Oracle Solaris 11.3 Linkers and Libraries Guide for more information.

2.3.1.5 The OPT Directive

The OPT directive requires that you specify SUN after !$PRAGMA.

The OPT directive sets the optimization level for a subprogram, overriding the level specified on the compilation command line. The directive must appear immediately before the target subprogram, and only applies to that subprogram. For example:

!$PRAGMA SUN OPT=2
        SUBROUTINE smart(a,b,c,d,e)
        ...etc

When the above is compiled with an f95 command that specifies -O4, the directive will override this level and compile the subroutine at -O2. Unless there is another directive following this routine, the next subprogram will be compiled at -O4.

The routine must also be compiled with the -xmaxopt[=n] option for the directive to be recognized. This compiler option specifies a maximum optimization value for PRAGMA OPT directives: if a PRAGMA OPT specifies an optimization level greater than the -xmaxopt level, the -xmaxopt level is used.

2.3.1.6 The PIPELOOP[=n] Directive

The PIPELOOP=n directive requires that you specify SUN after !$PRAGMA.

This directive must appear immediately before a DO loop. n is a positive integer constant, or zero, and asserts to the optimizer a dependence between loop iterations. A value of zero indicates that the loop has no inter-iteration (loop-carried) dependencies and can be freely pipelined by the optimizer. A positive n value implies that the I-th iteration of the loop has a dependency on the (I-n)-th iteration, and can be pipelined at best for only n iterations at a time. (Default if n is not specified is 0)

C    We know that the value of K is such that there can be no
C    cross-iteration dependencies (E.g. K>N)
!$PRAGMA SUN PIPELOOP=0
      DO I=1,N
       A(I)=A(I+K) + D(I)
       B(I)=B(I) + A(I)
      END DO

2.3.1.7 The PREFETCH Directives

The -xprefetch option flag, –xprefetch[=a[,a]], enables a set of PREFETCH directives that advise the compiler to generate prefetch instructions for the specified data element on processors that support prefetch.

!$PRAGMA SUN_PREFETCH_READ_ONCE(name)
!$PRAGMA SUN_PREFETCH_READ_MANY(name)
!$PRAGMA SUN_PREFETCH_WRITE_ONCE(name)
!$PRAGMA SUN_PREFETCH_WRITE_MANY(name)

See also the Oracle Developer Studio 12.5: C User’s Guide or the SPARC Architecture Manual, Version 9 for further information about prefetch instructions.

2.3.1.8 The ASSUME Directives

The ASSUME directive gives the compiler hints about conditions at certain points in the program. These assertions can help the compiler to guide its optimization strategies. The programmer can also use these directives to check the validity of the program during execution. There are two formats for ASSUME.

The syntax of the “point assertion” ASSUME is

!$PRAGMA ASSUME (expression [,probability])

Alternatively, the “range assertion” ASSUME is:

!$PRAGMA BEGIN ASSUME [expression [, probability)
     block of statements
!$PRAGMA END ASSUME

Use the point assertion form to state a condition that the compiler can assume at that point in the program. Use the range assertion form to state a condition that holds over the enclosed range of statements. The BEGIN and END pairs in a range assertion must be properly nested.

The required expression is a boolean expression that can be evaluated at that point in the program that does not involve user-defined operators or function calls except for those listed below.

The optional probability value is a real number from 0.0 to 1.0, or an integer 0 or 1, giving the probability of the expression being true. A probability of 0.0 (or 0) means never true, and 1.0 (or 1) means always true. If not specified, the expression is considered to be true with a high probability, but not a certainty. An assertion with a probability other than exactly 0 or 1 is a non-certain assertion. Similarly, an assertion with a probability expressed exactly as 0 or 1 is a certain assertion.

For example, if the programmer knows that the length of a DO loop is always greater than 10,000, giving this hint to the compiler can enable it to produce better code. The following loop will generally run faster with the ASSUME pragma than without it.

!$PRAGMA BEGIN ASSUME(__tripcount().GE.10000,1) !! a big loop
        do i = j, n
           a(i) = a(j) + 1
        end do
!$PRAGMA END ASSUME

Two intrinsic functions are available for use specifically in the expression clause of the ASSUME directive. (Note that their names are prefixed by two underscores.)

__branchexp()
Use in point assertions placed immediately before a branching statement with a boolean controlling expression. It yields the same result as the boolean expression controlling the branching statement.
__tripcount()
Yields the trip count of the loop immediately following or enclosed by the directive. When used in a point assertion, the statement following the directive must be the first line of a DO. When used in a range assertion, it applies to the outermost enclosed loop.

This list of special intrinsics might expand in future releases.

Use with the -xassume_control compiler option. (See –xassume_control[=keywords]) For example, when compiled with -xassume_control=check, the example above would produce a warning if the trip count ever became less than 10,000.

Compiling with -xassume_control=retrospective will generate a summary report at program termination of the truth or falsity of all assertions. See the f95 man page for details on -xassume_control.

Another example:

!$PRAGMA ASSUME(__tripcount.GT.0,1)
       do i=n0, nx

Compiling the above example with -xassume_control=check will issue a runtime warning should the loop not be taken because the trip count is zero or negative.

2.3.2 Parallelization Directives

OpenMP parallelization directives are only recognized when compiling with -openmp. Details regarding OpenMP parallelization can be found in the Oracle Developer Studio 12.5: OpenMP API User’s Guide.

The Fortran compiler supports the OpenMP API for shared memory parallelism, Version 4.0. Legacy Sun and Cray parallelization directives are now deprecated and should not be used.

2.3.2.1 OpenMP Parallelization Directives

The Fortran compiler recognizes the OpenMP API for shared memory parallelism as the preferred parallel programming model. The API is specified by the OpenMP Architecture Review Board (http://www.openmp.orghttp://www.openmp.org).

You must compile with the command-line option -xopenmp, to enable OpenMP directives. (see –xopenmp[={parallel|noopt|none}].)

For more information about the OpenMP directives accepted by f95, see the Oracle Developer Studio 12.5: OpenMP API User’s Guide.

2.3.2.2 Legacy Sun/Cray Parallelization Directives


Note -  Legacy Sun and Cray style parallelization directives are now deprecated. The OpenMP parallelization API is preferred.

2.3.3 IVDEP Directive

The !DIR$ IVDEP directive tells the compiler to ignore some or all loop-carried dependences on array references that it finds in a loop, allowing it to perform various loop optimizations such as microvectorization, distribution, software pipelining, among others, that would not be otherwise possible. It is employed in situations where the user knows either that the dependences do not matter or that they never occur in practice.

For example:

	 DO I = 1, N 
	   A(V(I)) = A(V(I)) + C(I) 
	 END DO        

In this loop there are several loop-carried dependences on A(V(I)), because V(I) may contain duplicate values to index A, and reordering the loop might result in different results. But if it is known that V contains only distinct values, the loop could be reordered safely, and an IVDEP directive could be used to allow optimization.

The —xivdep compiler option (see –xivdep[=p]) can be used to disable or determine the interpretation of IVDEP directives.

Some legacy interpretations of the IVDEP directive only assert that there are no backward loop-carried dependences. The Fortran compiler's default is —xivdep=loop, indicating that the IVDEP directive asserts there are no assumed loop dependences.

The following examples illustrate backward and forward dependences.

 	 do i = 1, n			! BACKWARD LOOP-CARRIED DEPENDENCE 
		... = a(i-1)		 ! S1 
	    a(i) = ...		 ! S2 
	 end do  
	 do i = 1, n			! FORWARD LOOP-CARRIED DEPENDENCE 
	    a(i) = ...		! S3 
		... = a(i-1)		! S4 
	 end do       

The first loop has a backward loop-carried dependence from S2 to S1, and the second loop has a forward loop-carried dependence from S3 to S4. Since the second loop has only a forward dependence, it can be distributed and/or microvectorized safely while the first one cannot.

Here is an example of the use of IVDEP under the default value of -xivdep=loop:

integer target a(n)
integer, pointer :: p(:), q(:)
!DIR$ IVDEP
do i = 1, n
	 p(i) = q(i) 
	 a(i) = a(i-1)
end do        

The assumed dependences between p(i) and q(i) and between p(i) and a(*) are ignored, but the obvious dependences between a(i) and a(i-1) are not. The loop can be divided into two loops and the resulting p(i) = q(i) loop can be microvectorized.

The IVDEP directive applies to the immediately following DO loop. No other code is allowed between the directive and the loop. !DIR$ IVDEP can also be applied to an array assignment, FORALL, or WHERE construct. If multiple directives are present for a particular loop (such as IVDEP and UNROLL), the compiler will obey all of them, if possible.