Previous | Contents | Index |
An interface block can be used to define generic assignment. The only procedures allowed in the interface block are subroutines that can be referenced as defined assignments.
The initial line for such an interface block takes the following form:
|
The subroutines within the interface block must have two nonoptional arguments, the first with intent OUT or INOUT, and the second with intent IN.
A defined assignment is treated as a reference to a subroutine. The left side of the assignment corresponds to the first dummy argument of the subroutine; the right side of the assignment corresponds to the second argument.
The ASSIGNMENT keyword extends or redefines an assignment operation if both sides of the equal sign are of the same derived type.
Defined elemental assignment is indicated by specifying ELEMENTAL in the SUBROUTINE statement.
Any procedure reference involving generic assignment must be resolvable to one specific procedure; it must be unambiguous. For more information, see Section 15.3.
The following is an example of a procedure interface block defining assignment:
INTERFACE ASSIGNMENT (=) SUBROUTINE BIT_TO_NUMERIC (NUM, BIT) INTEGER, INTENT(OUT) :: NUM LOGICAL, INTENT(IN) :: BIT(:) END SUBROUTINE BIT_TO_NUMERIC SUBROUTINE CHAR_TO_STRING (STR, CHAR) USE STRING_MODULE ! Contains definition of type STRING TYPE(STRING), INTENT(OUT) :: STR ! A variable-length string CHARACTER(*), INTENT(IN) :: CHAR END SUBROUTINE CHAR_TO_STRING END INTERFACE |
The following example shows two equivalent ways to reference subroutine BIT_TO_NUMERIC:
CALL BIT_TO_NUMERIC(X, (NUM(I:J))) X = NUM(I:J) |
The following example shows two equivalent ways to reference subroutine CHAR_TO_STRING:
CALL CHAR_TO_STRING(CH, '432C') CH = '432C' |
A CONTAINS statement separates the body of a main program, module, or external subprogram from any internal or module procedures it may contain. It is not executable.
The CONTAINS statement takes the following form:
|
Any number of internal procedures can follow a CONTAINS statement, but a CONTAINS statement cannot appear in the internal procedures themselves.
The ENTRY statement provides one or more entry points within a subprogram. It is not executable and must precede any CONTAINS statement (if any) within the subprogram.
The ENTRY statement takes the following form:
|
name
Is the name of an entry point. If RESULT is specified, this entry name must not appear in any specification statement in the scoping unit of the function subprogram.d-arg
Is a dummy argument. The dummy argument can be an alternate return indicator (*) if the ENTRY statement is within a subroutine subprogram.r-name
Is the name of a function result. This name must not be the same as the name of the entry point, or the name of any other function or function result. This parameter can only be specified for function subprograms.
ENTRY statements can only appear in external procedures or module procedures.
An ENTRY statement must not appear in a CASE, DO, IF, FORALL, or WHERE construct, or a nonblock DO loop.
When the ENTRY statement appears in a subroutine subprogram, it is referenced by a CALL statement. When the ENTRY statement appears in a function subprogram, it is referenced by a function reference.
An entry name within a function subprogram can appear in a type declaration statement.
Within the subprogram containing the ENTRY statement, the entry name must not appear as a dummy argument in the FUNCTION or SUBROUTINE statement, and it must not appear in an EXTERNAL or INTRINSIC statement. For example, neither of the following are valid:
(1) SUBROUTINE SUB(E) ENTRY E ... (2) SUBROUTINE SUB EXTERNAL E ENTRY E ... |
An ENTRY statement can reference itself if the function or subroutine subprogram was defined as RECURSIVE.
Dummy arguments can be used in ENTRY statements even if they differ in order, number, type and kind parameters, and name from the dummy arguments used in the FUNCTION, SUBROUTINE, and other ENTRY statements in the same subprogram. However, each reference to a function, subroutine, or entry must use an actual argument list that agrees in order, number, and type with the dummy argument list in the corresponding FUNCTION, SUBROUTINE, or ENTRY statement.
Dummy arguments can be referred to only in executable statements that follow the first SUBROUTINE, FUNCTION, or ENTRY statement in which the dummy argument is specified. If a dummy argument is not currently associated with an actual argument, the dummy argument is undefined and cannot be referenced. Arguments do not retain their association from one reference of a subprogram to another.
For specific information on ENTRY statements in function subprograms and subroutine subprograms (including examples), see Section 8.11.1 and Section 8.11.2, respectively.
If the ENTRY statement is contained in a function subprogram, it defines an additional function. The name of the function is the name specified in the ENTRY statement, and its result variable is the entry name or the name specified by RESULT (if any).
If the entry result variable has the same characteristics as the FUNCTION statement's result variable, their result variables identify the same variable, even if they have different names. Otherwise, the result variables are storage associated and must all be nonpointer scalars of intrinsic type, in one of the following groups:
Group 1 | Type default integer, default real, double precision real, default complex, double complex, or default logical |
Group 2 | Type REAL(16) and COMPLEX(16) |
Group 3 | Type default character (with identical lengths) |
All entry names within a function subprogram are associated with the name of the function subprogram. Therefore, defining any entry name or the name of the function subprogram defines all the associated names with the same data type. All associated names with different data types become undefined.
If RESULT is specified in the ENTRY statement and RECURSIVE is specified in the FUNCTION statement, the interface of the function defined by the ENTRY statement is explicit within the function subprogram.
The following example shows a function subprogram that computes the hyperbolic functions SINH, COSH, and TANH:
REAL FUNCTION TANH(X) TSINH(Y) = EXP(Y) - EXP(-Y) TCOSH(Y) = EXP(Y) + EXP(-Y) TANH = TSINH(X)/TCOSH(X) RETURN ENTRY SINH(X) SINH = TSINH(X)/2.0 RETURN ENTRY COSH(X) COSH = TCOSH(X)/2.0 RETURN END |
On the RESULT keyword, see Section 8.5.2.1.
8.11.2 ENTRY Statements in Subroutine Subprograms
If the ENTRY statement is contained in a subroutine subprogram, it defines an additional subroutine. The name of the subroutine is the name specified in the ENTRY statement.
If RECURSIVE is specified on the SUBROUTINE statement, the interface of the subroutine defined by the ENTRY statement is explicit within the subroutine subprogram.
The following example shows a main program calling a subroutine containing an ENTRY statement:
PROGRAM TEST ... CALL SUBA(A, B, C) ! A, B, and C are actual arguments ... ! passed to entry point SUBA END SUBROUTINE SUB(X, Y, Z) ... ENTRY SUBA(Q, R, S) ! Q, R, and S are dummy arguments ... ! Execution starts with this statement END SUBROUTINE |
The following example shows an ENTRY statement specifying alternate returns:
CALL SUBC(M, N, *100, *200, P) ... SUBROUTINE SUB(K, *, *) ... ENTRY SUBC(J, K, *, *, X) ... RETURN 1 RETURN 2 END |
Note that the CALL statement for entry point SUBC includes actual alternate return arguments. The RETURN 1 statement transfers control to statement label 100 and the RETURN 2 statement transfers control to statement label 200 in the calling program.
On implementation of argument association in ENTRY statements, see the HP Fortran for OpenVMS User Manual.
This chapter describes:
Intrinsic procedures are functions and subroutines that are included in the Fortran 95/90 library. There are four classes of intrinsic procedures:
Intrinsic procedures are invoked the same way as other procedures, and follow the same rules of argument association.
The intrinsic procedures have generic (or common) names, and many of the intrinsic functions have specific names. (Some intrinsic functions are both generic and specific.)
In general, generic functions accept arguments of more than one data type; the data type of the result is the same as that of the arguments in the function reference. For elemental functions with more than one argument, all arguments must be of the same type (except for the function MERGE).
When an intrinsic function is passed as an actual argument to a procedure, its specific name must be used, and when called, its arguments must be scalar. Some specific intrinsic functions are not allowed as actual arguments in all circumstances. Table 9-1 lists specific functions that cannot be passed as actual arguments.
AIMAX0 | EOF | JIDINT | MAX0 |
AIMIN0 | FLOAT | JIFIX | MAX1 |
AJMAX0 | FLOATI | JINT | MIN0 |
AJMIN0 | FLOATJ | JMAX0 | MIN1 |
AKMAX0 | FLOATK | JMAX1 | MULT_HIGH |
AKMIN0 | ICHAR | JMIN0 | MY_PROCESSOR |
AMAX0 | IDINT | JMIN1 | NUMBER_OF_PROCESSORS |
AMAX1 | IFIX | KIDINT | NWORKERS |
AMIN0 | IIDINT | KIFIX | PROCESSORS_SHAPE |
AMIN1 | IIFIX | KINT | QCMPLX |
CHAR | IINT | KIQINT | QEXT |
CMPLX | IMAX0 | KIQNNT | QEXTD |
DBLE | IMAX1 | KMAX0 | QMAX1 |
DBLEQ | IMIN0 | KMAX1 | QMIN1 |
DCMPLX | IMIN1 | KMIN0 | QREAL |
DFLOTI | INT | KMIN1 | RAN |
DFLOTJ | INT_PTR_KIND | LGE | REAL |
DFLOTK | INT1 | LGT | SECNDS |
DMAX1 | INT2 | LLE | SIZEOF |
DMIN1 | INT4 | LLT | SNGL |
DPROD | INT8 | LOC | SNGLQ |
DREAL | JFIX | MALLOC | ZEXT |
For all intrinsic procedures, the arguments shown are the names you must use as keywords when using the keyword form for actual arguments. For example, a reference to function CMPLX (X, Y, KIND) can be written as follows:
Using positional arguments: | CMPLX (F, G, L) |
Using argument keywords: | CMPLX (KIND=L, Y=G, X=F) 1 |
Some argument keywords are optional (denoted by square brackets). The following describes some of the most commonly used optional arguments:
BACK | Specifies that a string scan is to be in reverse order (right to left). |
DIM | Specifies a selected dimension of an array argument. |
KIND | Specifies the kind type parameter of the function result. |
MASK | Specifies that a mask can be applied to the elements of the argument array to exclude the elements that are not to be involved in an operation. |
Examples
The syntax for the DATE_AND_TIME intrinsic subroutine shows four optional positional arguments: DATE, TIME, ZONE, and VALUES (see Section 9.4.36).
The following shows some valid ways to specify these arguments:
! Keyword example CALL DATE_AND_TIME (ZONE=Z) ! The following two positional examples are equivalent CALL DATE_AND_TIME (DATE, TIME, ZONE) CALL DATE_AND_TIME (, , ZONE) |
This section describes the categories of generic intrinsic functions (including a summarizing table), lists the intrinsic subroutines, and provides general information on bit functions.
Intrinsic procedures are fully described (in alphabetical order) in
Section 9.4.
9.3.1 Categories of Intrinsic Functions
Generic intrinsic functions can be divided into categories, as shown in Table 9-2.
Category | Subcategory | Description |
---|---|---|
Numeric | Computation | Perform type conversions or simple numeric operations: ABS, AIMAG, AINT, AMAX0, AMIN0, ANINT, CEILING, CMPLX, CONJG, DBLE, DCMPLX, DFLOAT, DIM, DPROD, DREAL, FLOAT, FLOOR, IFIX, IMAG, INT, MAX, MAX1, MIN, MIN1, MOD, MODULO, NINT, QCMPLX, QEXT, QFLOAT, QREAL, RAN, REAL, SIGN, SNGL, ZEXT |
Manipulation 1 | Return values related to the components of the model values associated with the actual value of the argument: EXPONENT, FRACTION, NEAREST, RRSPACING, SCALE, SET_EXPONENT, SPACING | |
Inquiry 1 | Return scalar values from the models associated with the type and kind parameters of their arguments 2: DIGITS, EPSILON, HUGE, ILEN, MAXEXPONENT, MINEXPONENT, PRECISION, RADIX, RANGE, SIZEOF, TINY | |
Transformational |
Perform vector and matrix multiplication:
DOT_PRODUCT, MATMUL |
|
System |
Return information about a process or processor:
PROCESSORS_SHAPE, NWORKERS,
MY_PROCESSOR, NUMBER_OF_PROCESSORS, SECNDS |
|
Kind type | Return kind type parameters: SELECTED_INT_KIND, SELECTED_REAL_KIND, KIND | |
Mathematical | Perform mathematical operations: ACOS, ACOSD, ASIN, ASIND, ATAN, ATAND, ATAN2, ATAN2D, COS, COSD, COSH, COTAN, COTAND, EXP, LOG, LOG10, SIN, SIND, SINH, SQRT, TAN, TAND, TANH | |
Bit | Manipulation | Perform single-bit processing, and logical and shift operations; and allow bit subfields to be referenced: AND, BTEST, IAND, IBCHNG, IBCLR, IBITS, IBSET, IEOR, IOR, ISHA, ISHC, ISHFT, ISHFTC, ISHL, LSHIFT, NOT, OR, RSHIFT, XOR |
Inquiry | Lets you determine parameter s (the bit size) in the bit model 3: BIT_SIZE | |
Representation | Return information on bit representation of integers: LEADZ, POPCNT, POPPAR, TRAILZ | |
Character | Comparison | Lexically compare character-string arguments and return a default logical result: LGE, LGT, LLE, LLT |
Conversion | Convert character arguments to integer, ASCII, or character values 4: ACHAR, CHAR, IACHAR, ICHAR | |
String handling | Perform operations on character strings, return lengths of arguments, and search for certain arguments: ADJUSTL, ADJUSTR, INDEX, LEN_TRIM, REPEAT, SCAN, TRIM, VERIFY | |
Inquiry | Returns length of argument: LEN | |
Array | Construction | Construct new arrays from the elements of existing array: MERGE, PACK, SPREAD, UNPACK |
Inquiry | Let you determine if an array argument is allocated, and return the size or shape of an array, and the lower and upper bounds of subscripts along each dimension: ALLOCATED, LBOUND, SHAPE, SIZE, UBOUND | |
Location | Returns the geometric locations of the maximum and minimum values of an array: MAXLOC, MINLOC | |
Manipulation | Let you shift an array, transpose an array, or change the shape of an array: CSHIFT, EOSHIFT, RESHAPE, TRANSPOSE | |
Reduction | Perform operations on arrays. The functions "reduce" elements of a whole array to produce a scalar result, or they can be applied to a specific dimension of an array to produce a result array with a rank reduced by one: ALL, ANY, COUNT, MAXVAL, MINVAL, PRODUCT | |
Miscellaneous |
Do the following:
|
Previous | Next | Contents | Index |