next up previous contents index
Next: B. Fortran 95 Up: ADAPTOR HPF Language Reference Previous: N. ADAPTOR Specific Directives   Contents   Index

Subsections


A. Appendix: Fortran 90

This appendix gives a short summary of new features in Fortran 90. It was adopted in 1991 and is now an ANSI and the ISO standard.

A..1 Syntax Improvements

A..2 Dynamic Arrays

Fortran 90 supports two kinds of dynamic arrays:

While the allocatable arrays use heap storage, automatic arrays can use stack storage.


A..2.1 Allocatable Arrays

An allocatable array is always local (it cannot be a dummy argument or be declared in common). It can be allocated and deallocated only locally. This kind of array will be used if user input specifies the size of the arrays at runtime.

   REAL, ALLOCATABLE :: a(:), b(:)
   READ *, n
   IF (n .GT. 0) THEN
      ALLOCATE (a(n), b(n))
      ...
      DEALLOCATE (b, a)
   END IF


A..2.2 Automatic Arrays

An automatic array can appear only in a subprogram. It looks similar to a static array but the bounds are specified as dummy arguments or elements of a common block. In any case, an automatic array is not a dummy array and not part of a common block.

   SUBROUTINE s (n)
   REAL a(n), b(n)
   ...
   a(2:n) = b(1:n-1)

A..3 Array Syntax

Array syntax allows to specify operations on full arrays or an sections of them.

      real, dimension(1:100,1:100) :: A, B, C     ! Declare Arrays
      real, dimension(1:50)        :: X, Y        ! Declare vectors
      A = 1.0                       ! assign whole array
      B = 2.0
      C = A * B                     ! combine whole arrays
      X = C(1,1:100:2)              ! pick alternate elements from row 1
      Y(1:50:-1) = X(1:50)          ! reverse order of vector

The WHERE construct works as a masking operation for array statements. It can be used as a single statement thus:

      WHERE (A >= 0.0) A = SQRT (A)

or as a block WHERE construct such as

      WHERE (mask)
         A = SQRT (A)
       ELSE WHERE
         A = default
      END WHERE

An array value can be formed with an array constructor (is always a one-dimensional array).

      parameter (n=6)
      real a(n)
      ...
      A = (/(i=1,n)/)
      A = [1:n]
      A = [13:43:5]
      A = [1,2,3,4,5,6]
      A = (/ 2, 3, 4, (I, I = 13, 43, 5) /)   ! not supported
      A = [2, 3, 4, [13:43:5]]                ! not supported


A..4 Array-valued Functions

With Fortran 90, functions can return full arrays instead of only scalar variables.

      function iota (n)
      integer n
      integer iota (n)
      iota = (/(i,i=1,n)/)
      end


A..5 Assumed-Shaped Arrays

A dummy array is an assumed-shaped array if there are no declared bounds for it. The bounds will be passed in a data descriptor for the array. Intrinsic functions are provided to query the bounds.

       subroutine init (A)
       real A(:,:)
       do j = lbound(A,2), ubound(A,2)
         do i = lbound(A,1), ubound(A,1)
            A(i,j) = 1.0
         end do
       end do

A..6 New Control Structures

The new control constructs of Fortran 90 can be used with ADAPTOR. They will be translated to equivalent FORTRAN 77 constructs.

      do
         read *, number
         print *, "input data: ", number
         if (number < 0) then
            exit
         else if (mod(number, 2) == 0) then
            cycle
         else
            number_of_odd_numbers = number_of_odd_numbers + 1
         end if
      end do

      print *, "enter traffic_light color"
      read *, traffic_light
      select case(traffic_light)
      case ("red")
      print *, "stop"
      case ("yellow")
      print *, "caution"
      case ("green")
      print *, "go"
      case default
      print *, "illegal value:", traffic_light
      end select


A..7 Parameterized Data Types

Portability of numerical code has long been difficult, primarily due to differences in the word sizes of the computers on which the code is run. Fortran 90 introduces parameterized types, increasing portability of software from machine to machine. This is done using kind values, constants associated with an intrinsic type such as integer or real. Parameterization of kind values allows precision changes by changing a single constant in the program. Several intrinsic functions are provided to select kind values based on the range and precision desired and inquire about a variable's precision characteristics in a portable way.

module Precision
   integer, parameter :: Q = selected_real_kind( 10, 10 )
end module Precision

program Portable
  real (kind=Q) :: a, b, c
  ...
end program Portable

The selected_real_kind function above selects the kind value corresponding to a real number with at least 10 decimal digits of precision and a decimal exponent range of at least 10 in magnitude. The selected_int_kind function is similar, and an expression such as selected_int_kind(10) selects the kind value corresponding to a integer number with magnitude in the range $(10^{-10}, 10^{10})$.

A..8 Numerical Inquiry and Manipulation Functions

Fortran 90 introduces several intrinsic functions to inquire about machine dependent characteristics of an integer or real. For example, the inquiry function, huge, can be used to find the largest machine representable number for an integer or real value. The integer model used by these inquiry functions is1

\begin{displaymath}
i = s \sum_{k=0}^{q-1} d_k r^k
\end{displaymath}


where 

$i$ is the integer value
$s$ is the sign (+1 or -1)
$r$ is the radix ($r > 1$)
$q$ is the number of digits ($q > 0$)
$d_k$ is the $k$th digit, $0 \le d_k < r$.
The floating-point model used by the inquiry functions is

\begin{displaymath}
x = s b^e \sum_{k=1}^{p} f_k b^{-k}
\end{displaymath}


where 

$x$ is the real value
$s$ is the sign (+1 or -1)
$b$ is the base ($b > 1$)
$e$ is the exponent
$p$ is the number of mantissa digits ($p > 1$)
$f_k$ is the $k$th digit, $0 \le f_k < b$, $f_1 = 0 \Rightarrow f_k = 0 \: \forall \: k$.

Table 2 lists intrinsic functions that inquire about the numerical environment. Table 3 lists intrinsic functions that manipulate the numerical characteristics of variables in the real model. An important feature of all of these intrinsic functions is that they are generic and may be used to obtain information about any kind of integer or real supported by the Fortran 90 implementation.


Table 2: Numeric Inquiry Functions
Function Description
digits(x) $q$ for an integer argument, $p$ for a real argument
epsilon(x) $b^{1-p}$ for a real argument
huge(x) Largest in the integer or real model
minexponent(x) Minimum value of $e$ in the real model
maxexponent(x) Maximum value of $e$ in the real model
precision(x) Decimal precision (real or complex)
radix(x) The base $b$ of the integer or real model
range(x) Decimal exponent range (real, complex, or integer)
tiny(x) Smallest positive value in the real model



Table 3: Numeric Manipulation Functions
Function Description
exponent(x) Value of $e$ in the real model
fraction(x) Fractional part in the real model
nearest(x) Nearest processor number in a given direction
rrspacing(x) Reciprocal of relative spacing near argument
set_exponent(x) Set the value of $e$ to a specified value
spacing(x) Model absolute spacing near the argument


ADAPTOR supports the numeric inquiry and the numeric manipulation functions. The use of the numeric manipulation functions will require a Fortran 90 compiler on the target machine.


A..9 Interface Blocks

In FORTRAN 77 interfaces are always implicit. In Fortran 90 interfaces can be explicit:

       interface
         subroutine SUB (A, B)
         real A(:,:)
         integer, pointer :: B
         end
       end interface
       ...
       call SUB (X, Y)    ! pass descriptor for X instead of pointer

Certain uses (such as POINTER dummies and assumed-shape array dummies, optional arguments) require an explicit interface.


A..10 Optional Arguments

In Fortran 90 it is possible to indicate that certain arguments to a procedure are optional arguments in the sense that they do not have to be present when the procedure is called. An optional argument must be declared to be such by the OPTIONAL attribute.

      SUBROUTINE DOIT (M, N, S, D)
      INTEGER N
      REAL S, D
      INTEGER, OPTIONAL :: M
      ...
      END SUBROUTINE DOIT

In the example the argument M must not be available. The subroutine can be called with any of the following statements:

      call DOIT (0, 7000, 0.1, 100.0)
      call DOIT (0, 7000, D=0.1, S=100.0)
      call DOIT (N=7000, D=0.1, S=100.0)
      call DOIT (D=0.1, S=100.0, N=7000)
      call DOIT (M=0, N=7000, D=0.1, S=100.0)

The presence of an optional argument can be tested with the intrinsic inquiry function PRESENT.

Optional arguments can be used within ADAPTOR. It should be observed that for user functions explicit interface blocks should be available if optional arguments are given.


A..11 Derived Data Types

The user can define new data types, created from a collection of intrinsic types. These are similar to the concept of structures or records in other languages.

      type POINT
         integer :: X, Y
      end type

Objects of a derived data type can be defined in the following way:

       TYPE(POINT) :: P1, P2
       ...
       P1%X = 0.0; P1%Y = 0.0
       P2   = P1;

By overloading existing operators it is possible to define new operations on derived data types (see section A.16).


A..12 Pointers

In Fortran 90 objects can have the POINTER attribute. No storage will be allocated for such an object. The object can be pointer associated to an existing object or to an object that will be created with the ALLOCATE statement.

       real, pointer :: P
       real, target  :: X
       ...
       P => X         ! P is associated with X
       P = 5.3
       print *, X     ! will print the value 5.3
       allocate (P)   ! P is associated with a new real variable
       ...
       deallocate (P) ! give memory free to which P is associated

If a pointer is associated with an existing variable, this variable must have the TARGET attribute or must be itself an associated pointer. A pointer can also be an alias to a row or column of an array.

      real, target, dimension (N,N) :: A
      real, pointer, dimension (:) :: P
      ....
      P => A(3,:)     ! P is an alias to the third row of A
      P => A(:,5)     ! P is an alias to the fifth column of A

The ASSOCIATED intrinsic function checks whether a pointer is associated with a particular target, or with any target.

A component of a derived type can be a pointer. By this way, it is now possible to have dynamic data structures in Fortran programs.


A..13 Modules

Common blocks in FORTRAN 77 were the only portable means of achieving global access of data throughout a collection of subprograms. This is unsafe, error-prone, and encourages bad programming practices in general. Fortran 90 provides a new program unit, a module, that replaces the common block and also provides many other features that allow modularization and data hiding, key concepts in developing large, maintainable numerical code.

Modules consist of a set of declarations and module procedures that are grouped under a single global name available for access in any other program unit via the use statement. Interfaces to the contained module procedures are explicit and permit compile time type-checking in all program units that use the module. Visibility of items in a module may be restricted by using the private attribute. The public attribute is also available. Those identifiers not declared private in a module implicitly have the public attribute.

module TypicalModule
   private SWAP   ! Make swap visible only within this module.
 
   contains
 
   subroutine ORDER (X, Y)   ! Public by default.
      integer, intent( inout ) :: X, Y
 
      if ( abs( x ) < abs( y ) )  call SWAP (x, y)
   end subroutine order
 
   subroutine SWAP (X, Y)
      integer, intent( inout ) :: X, Y
      integer TMP
 
      TMP = X; X = Y; Y = TMP ! Swap X and Y.
   end subroutine SWAP

end module TypicalModule
 
program UseTypicalModule
   use TypicalModule
 
   ! Declare and initialize x and y.
   integer :: x = 10, y = 20
 
   print *, x, y
   call ORDER ( x, y )
   print *, x, y
end program UseTypicalModule

A module collects also all interfaces in one place. The USE statement imports also the interfaces.

A..14 Internal Procedures

In FORTRAN 77, all subprograms are external with the exception of statement functions. Internal subprograms are now possible under Fortran 90 and achieve an effect similar to FORTRAN 77's statement functions. They are visible only within the containing program and have an explicit interface, guarding against type mismatches in calls to the subprogram. Internal subprograms must be separated from the main program by the contains statement. An example illustrating an internal subprogram is given below.

program LAPLACE
 
implicit none
 
! global data
 
   real, allocatable :: F(:,:), DF(:,:)
   integer MAXX, MAXY
   ...
   call ALLOC_DATA ()
   call INIT ()
   ...
   call FREE_DATA ()

contains
 
  subroutine ALLOC_DATA ()
     read *,MAXX, MAXY
     allocate (F(MAXX,MAXY), DF(1:MAXX,MAXY))
  end subroutine ALLOC_DATA

  subroutine FREE_DATA ()
     deallocate (DF, F)
  end subroutine FREE_DATA
 
  subroutine INIT ()
     F = 2.
     F(:,MAXY) = 1.
     F(2:MAXX-1,2:MAXY-1) =  0
     DF = 0
  end subroutine INIT
 
end program LAPLACE

When procedures are internal to a program, another procedure, or within a module, they are preceded by a CONTAINS statement. The internal procedure must appear just before the last END statement of the program, procedure, or module containing them.


A..15 Generic Procedures

       interface SWAP    ! generic name

          subroutine SWAP_INT (I, J)    ! specific name
          integer I, J
          end subroutine SWAP_INT

          subroutine SWAP_REAL (X, Y)   ! specific name
          real X, Y
          end subroutine SWAP_REAL

       end interface


A..16 Overloading

Fortran 90 allows to overload existing operators. By this way, it is possible to extend the operations for new defined types.

      MODULE points
      TYPE point
         INTEGER :: x, y
      END TYPE
      INTERFACE OPERATOR (+)
         MODULE PROCEDURE add_points
      END INTERFACE

      CONTAINS

      TYPE (point) FUNCTION add_points (x, y)
      TYPE (point) x, y
      ...
      END FUNCTION add_points
      ...
      END MODULE POINTS

      SUBROUTINE s
      USE points
      TYPE (point) :: p1, p2, p3
      ...
      p3 = p1 + p2
      ...
      END SUBROUTINE s


next up previous contents index
Next: B. Fortran 95 Up: ADAPTOR HPF Language Reference Previous: N. ADAPTOR Specific Directives   Contents   Index
Thomas Brandes 2004-03-18