|
Документ взят из кэша поисковой машины. Адрес
оригинального документа
: http://star.arm.ac.uk/f77to90/a3.html
Дата изменения: Sat Feb 17 19:25:36 1996 Дата индексирования: Mon Oct 1 20:56:09 2012 Кодировка: |
The underline symbol _ is permitted inside the names of variables, and the length of variables must have at most 31 characters (instead of at most 6 in the Fortran 77 standard).
Blanks become significant in the free form of the source code. Old commands like ENDIF and GOTO can also in the future be written either as END IF or GO TO respectively, but of course not like EN DIF or GOT O. To permit significant blanks in the old (fixed) form of the source code would not be possible, since it for example is permitted to write END in the following silly way
E N D
INCLUDE can be used to include source code from an external file.
The construct is a line where there is INCLUDE and a character string
and, perhaps, some concluding comments. Interpretation is
implementation-dependent, normally the character string is treated as
the name of the file that holds the source code that should be
included. Nesting is permitted (and the number of levels is
implementation-dependent), but recursion is not permitted for the
INCLUDE statement.
As in most Algol-type languages the word END can be complemented with the name of the routine or function like END FUNCTION GAMMA.
< .LT. > .GT.
<= .LE. >= .GE.
== .EQ. /= .NE.
REAL, DIMENSION (3), PARAMETER :: &
a = (/ 0.0, 0.0, 0.0 /), b = (/ 1.0, 1.0, 1.0 /)
COMPLEX, DIMENSION(10) :: john
while the variables a and b become constant vectors with 3 elements
and the floating-point values 0.0 and 1.0, respectively, while john
becomes a complex vector with 10 complex elements, not yet assigned
any values.
If you wish to use the Algol principle to specify all variables, this is simplified by the command IMPLICIT NONE which switches off the implicit-type rules.
Double precision has been implemented with a more general method to give the desired precision, namely the parameter KIND for which precision we wish, useful on all variable types.
INTEGER, PARAMETER :: LP = SELECTED_REAL_KIND(20)
REAL (KIND = LP) :: X, Y, Z
The above two statements thus declare the variables X, Y
and Z to
be REAL floating-point variables with at least 20 decimal digits
accuracy with a data type that is called LP (where LP stands
for LONG PRECISION).
SELECT CASE (expression)
CASE block-switch
block
CASE block-switch
block
CASE DEFAULT
default block
END SELECT
Typical construct:
SELECT CASE(3*I-J) ! the control variable is 3*i-j
CASE(0) ! for the value zero
: ! you execute the code here
CASE(2,4:7) ! for the variables 2, 4, 5, 6, 7
: ! you execute the code here
CASE DEFAULT ! and for all other values
! you execute the code here
: !
END SELECT
If the CASE DEFAULT is missing and none of the alternatives is valid,
the execution continues directly with the next statement following the
END SELECT, without any error message.
Another example:
INTEGER FUNCTION SIGNUM(N)
SELECT CASE (N)
CASE (:-1)
SIGNUM = -1
CASE (0)
SIGNUM = 0
CASE (1:)
SIGNUM = 1
END SELECT
END
name: DO
executable statements
END DO name
The usual DO-loop has the following new simplified form without
statement number,
name: DO i = integer_expr_1, integer_expr_2 ,integer_expr_3
executable statements
END DO name
where i is called control variable, and where
,integer_expr_3 is optional.
Finally there is also the DO WHILE loop
name: DO WHILE (logical_expression)
executable statements
END DO name
The name is optional but can be used for nested loops in order to
indicate which one that is to be iterated once again with the CYCLE
statement or terminated with the EXIT statement.
S1: DO
IF (X > Y ) THEN
Z = X
EXITS1
END IF
CALL NEW(X)
END DO
N = 0
LOOP1: DO I = 1, 10
J= I
LOOP2: DO K =1, 5
L = K
N = N +1
END DO LOOP2
END DO LOOP1
In the latter case the final values from the variables will be as
follows, in full accordance with the standard, I = 11, J = 10, K = 6,
L = 5, and N = 50.
To name the loop is completely optional. Also note that this type of name is limited to DO-loop, CASE or IF...THEN...ELSE...ENDIF constructs. The old possibilities with statement numbers are still available, also in the free form.
SUBROUTINE solve (a, b, n)
REAL, OPTIONAL, INTENT (IN) :: b
can be called with
CALL solve (n = i, a = x)
where two of the arguments are given with keywords instead of position
and where the third one has a default value. If SOLVE is an external
routine it requires making use of an INTERFACE block in the calling
program. Routines can be specified to be recursive.
RECURSIVE FUNCTION factorial (n) RESULT (fac)but must then have a special RESULT name in order to return the result.
a = ''
and assignment of an overlapping string is now permitted
a(:5) = a(3:7)
The new intrinsic function TRIM which removes concluding blanks is an
important addition. You can now make a free choice between the
apostrophe ' and the quotation mark " in order to indicate a character
string. This can among other things be used in such a way that if you
wish to write an apostrophe inside the text, then you use the
quotation mark as indicators, and in the opposite case if you wish to
have a quotation mark inside the text you use the apostrophe as the
indicator.
NAMELIST /list2 / a, i, x
:
READ (unit, NML = list2)
which wishes to get input data of the following form, but all
variables do not have to given, and they can be given in any order.
&list2 X = 4.3, A = 1.E20, I = -4 /
REAL, DIMENSION(5,20) :: x, y
REAL, DIMENSION(-2:2,20) :: z
:
z = 4.0*y*sgrt(x)
We perhaps here wish to protect against negative elements of X.
This is done with the following construct
WHERE ( x >= 0.0 )
z = 4.0*y*sgrt(x)
ELSEWHERE
z = 0.0
END WHERE
Please note that ELSEWHERE has to be in one word! Compare also
with the function SUM which is discussed at the end of the next
section.
You can pick out a part of an array. Assume that the array A is specified in the following way.
REAL, DIMENSION(-4:0, 7) :: A
With A(-3, :) you pick the second row, while with
A(0:-4:-2, 1:7:2)
you pick (in reverse order) its each other element in each other column.
Just as variables can form arrays, also constants can form arrays.
REAL, DIMENSION(6) :: B
REAL, DIMENSION(2,3) :: C
B = (/ 1, 1, 2, 3, 5, 8 /)
C = RESHAPE( B, (/ 2,3 /) )
where the first argument to the intrinsic function RESHAPE gives the
value and the second argument gives the new shape. Two additional,
but optional, arguments are available to this function.
The above can also be written in a more compressed form using the PARAMETER attribute. In the first line below the PARAMETER attribute is compulsory (if the assignment is to be made on the same line), but in the second line it is optional. Remember that the PARAMETER attribute means that the quantity can not be changed during execution of the program.
REAL, DIMENSION(6), PARAMETER :: B = (/ 11, 12, 13, 14, 15, 16 /)
REAL, DIMENSION(2,3), PARAMETER :: C = RESHAPE( B, (/ 2, 3 /) )
Any statements for real parallel computation are not included in
Fortran 90. The committee believes it is necessary with additional
experience before the standardization of parallelization. See also
HPF discussed in the Appendix 8.
The second is to use an "allocatable array", i.e. with the statements ALLOCATE and DEALLOCATE you get and return a storage area for an array with type, rank and name (and possible other attributes) which had been specified earlier with the additional attribute ALLOCATABLE.
REAL, DIMENSION(:), ALLOCATABLE :: x : Allocate(x(N:M)) ! N and M are the integer expressions here. : x(j) = q ! Some assignment of the array. CALL sub(x) ! Use of the array in a subroutine. : DEALLOCATE (x)Deallocation occurs automatically (if the attribute SAVE has not been given) when you reach RETURN or END in the same program unit.
The third variant is an "automatic array", it is almost available in the old Fortran, where x in the example below has to be in the list of arguments. This is not required any more.
SUBROUTINE sub (i, j, k)
REAL, DIMENSION (i, j, k) :: x
Dimensions for x are taken from the integers in the calling
program.
Finally there is an "assumed-shape array" where the storage is
defined in the calling procedure and for which only the type, rank
and name are given.
SUBROUTINE sub(a)
REAL, DIMENSION (:,:,:) :: a
According to Metcalf and Reid (1990, 1992), section 6.3 you here
require an explicit interface. This has to look as follows
INTERFACE
SUBROUTINE SUB(A)
REAL, DIMENSION (:,:,:) :: A
END SUBROUTINE SUB
END INTERFACE
If you forget the INTERFACE or if you have an erroneous interface,
then you will usually get "segmentation error", it means that a
program unit may be missing.
Some intrinsic functions are available to determine the
actual dimension limits
DO (i = LBOUND(a,1), UBOUND(a,1))
DO (j = LBOUND (a,2), UBOUND (a,2))
DO (k = LBOUND(a,3),UBOUND (a,3))
where LBOUND gives the lower limit for the specified dimension and
UBOUND gives the upper one.
The sum of the positive value of a number of elements in an array is written
SUM ( X, MASK = X .GT. 0.0)
These statements can not be used in order to avoid division by zero
at for example summation of 1/X, that is the mask works only with
determining which numbers that are to be included in the summation,
and not whether a certain value has to be calculated or not. But in
this later case you can use the construct WHERE, see section 9.
The function SPREAD is discussed more fully in the solution of exercise (11.1).
All intrinsic functions and subroutines are discussed in Appendix 5.
TYPE staff_member
CHARACTER(LEN=20) :: first_name, last_name
INTEGER :: identification, department
END TYPE
which can be used in order to describe an individual. A combination of
individuals can also be formed
TYPE(staff_member), DIMENSION(100) :: staffIndividuals can be referred to as staff(number) and a field can be referred as staff(number)%first_name. You can also nest definitions
TYPE company
CHARACTER(LEN=20) :: company_name
TYPE(staff_member), DIMENSION(100) :: staff
END TYPE
:
TYPE(company), DIMENSION(10) :: several_companies
A numerically more interesting example is a sparse matrix A with at
most one hundred non-zero elements, which can be specified with the
following statement
TYPE NONZERO
REAL VALUE
INTEGER ROW, COLUMN
END TYPE
and
TYPE (NONZERO) :: A(100)
You then get the value of A(10) by writing
A(10)%VALUE.
Assignment can be done, for example with
A(15) = NONZERO(17.0,3,7)In order to use user-defined data types in for example COMMON, or to make sure that two data types which look the same are treated as identical, you can use the SEQUENCE statement, in the latter case it is also required that no variable is specified PRIVATE.
B'01010101010101010101010101010101'
for binary,
O'01234567'
for octal, and
Z'ABCDEF'
for hexadecimal numbers.
Pointers are discussed in chapter 12.