ABSTRACT
keyword, i.e.
ABSTRACT INTERFACEEach interface body in an abstract interface block defines an abstract interface instead of declaring a procedure. The name of an abstract interface can be used in the procedure declaration statement to declare a specifc procedure with that interface, e.g.
PROCEDURE(aname) :: spec1, spec2declares
SPEC1
and SPEC2
to be procedures with the interface
(i.e. type, arguments, etc.) defined by the abstract interface ANAME
.
The procedure declaration statement can also be used with the name of any procedure that has an explicit interface, e.g.
PROCEDURE(x) ydeclares
Y
to have the same interface as X
.
Also, procedures with implicit interfaces can be declared by using
PROCEDURE
with a type specification instead of a name, or by omitting
the name altogether.
The following attributes can be declared at the same time on the procedure
declaration statement: BIND(C
...)
,
INTENT(
intent)
,
OPTIONAL
, POINTER
, PRIVATE
, PUBLIC
, SAVE
.
For example,
PROCEDURE(aname),PRIVATE :: spec3
Note that POINTER
declares a procedure pointer (see next section),
and that INTENT
and SAVE
are only allowed for procedure pointers
not for ordinary procedures.
The NAG Fortran Compiler also allows the PROTECTED
attribute to be
specified on the procedure declaration statement: this is an extension to
the published Fortran 2003 standard.
POINTER
attribute; it
may be a named pointer or a structure component (the latter are described
elsewhere).
The usual way of declaring a procedure pointer is with the procedure
declaration statement, by including the POINTER
clause in that
statement: for example,
PROCEDURE(aname),POINTER :: p => NULL()declares
P
to be a procedure pointer with the interface ANAME
,
and initialises it to be a disassociated pointer.
A named procedure pointer may also be declared by specifying the POINTER
attribute in addition to its normal procedure declaration: for example,
a function declared by a type declaration statement will be a function pointer
if the POINTER
attribute is included in the type declaration:
REAL, EXTERNAL, POINTER :: funptrThe POINTER statement can also be used to declare a procedure pointer, either in conjunction with an interface block, an
EXTERNAL
statement, or
a type declaration statement, for example:
INTERFACE SUBROUTINE sub(a,b) REAL,INTENT(INOUT) :: a,b END SUBROUTINE END INTERFACE POINTER sub
Procedure pointers may also be stored in derived types as procedure pointer components. The syntax and effects are slightly different, making them act like “object-bound procedures”, and as such are described in the object-oriented programming section.
There are five standard modules in Fortran 2003: IEEE_ARITHMETIC, IEEE_EXCEPTIONS, IEEE_FEATURES, ISO_C_BINDING and ISO_FORTRAN_ENV.
A program is permitted to have a non-intrinsic module with the same name as
that of an intrinsic module: to this end, the USE
statement has been
extended: ‘USE,INTRINSIC ::
’ specifies that an intrinsic module
is required, whereas ‘USE,NON_INTRINSIC ::
’ specifies that a
non-intrinsic module is required.
If these are not used, the compiler will select an intrinsic module only if
no user-defined module is found.
For example,
USE,INTRINSIC :: iso_fortran_envuses the standard intrinsic module
ISO_FORTRAN_ENV
, whereas
USE,NON_INTRINSIC :: iso_fortran_envuses a user-defined module with that name. Note that the double-colon ‘
::
’ is required if either
specifier is used.
USE my_module, OPERATOR(.localid.)=>OPERATOR(.remotename.)would import everything from
MY_MODULE
, but the .REMOTENAME.
operator would have its name changed to .LOCALID.
.
Note that this is only available for user-defined operator names; the
intrinsic operators .AND.
et al cannot have their names changed in this
way, nor can ASSIGNMENT(=)
be renamed.
The local name must be an operator if and only if the remote (module entity)
name is an operator: that is, both of
USE my_module, something=>OPERATOR(.anything.) USE my_module, OPERATOR(.something.)=>anythingare invalid (a syntax error will be produced).
ISO_FORTRAN_ENV
is now available.
It contains the following default INTEGER
named constants.
CHARACTER_STORAGE_SIZE
ERROR_UNIT
FILE_STORAGE_SIZE
RECL=
in bits.
INPUT_UNIT
*
’) unit number for READ
.
IOSTAT_END
IOSTAT=
return value for end-of-file.
IOSTAT_EOR
IOSTAT=
return value for end-of-record.
NUMERIC_STORAGE_SIZE
OUTPUT_UNIT
PRINT
, the same as the ‘*
’ unit for
WRITE
.
IMPORT
statement has been added.
This has the syntax
IMPORT
[ [ ::
] name [ ,
name ]... ]
The IMPORT
statement must follow any USE
statements and precede
all other declarations, in particular, IMPLICIT
and PARAMETER
statements.
Anything imported with IMPORT
must have been declared prior to the
interface body.
[ ]
) can now ([5.1]) be used in place of the
parenthesis-slash pairs ((/ /)
) for array constructors.
This allows expressions to be more readable when array constructors are
being mixed with ordinary parentheses.
RESHAPE((/(i/2.0,i=1,100)/),(/2,3/)) ! Old way RESHAPE([(i/2.0,i=1,100)],[2,3]) ! New way
Array constructors may now ([5.2]) begin with a type specification followed by
a double colon (::
); this
makes zero-sized constructors easy (and eliminates potential ambiguity with
character length), and also provides assignment conversions thus eliminating
the need to pad all character strings to the same length.
[ Logical :: ] ! Zero-sized logical array [ Double Precision :: 17.5, 0, 0.1d0 ] ! Conversions [ Character(200) :: 'Alf', 'Bernadette' ] ! Padded to length 200
A fourth enhancement is made in the Fortran 2008 standard: a value can be omitted for a component that is allocatable.
This makes structure constructors more like built-in generic functions that can be overridden when necessary. Here is an example showing all three enhancements.
TYPE quaternion REAL x=0,ix=0,jx=0,kx=0 END TYPE ... INTERFACE quaternion MODULE PROCEDURE quat_from_complex END INTERFACE ... TYPE(quaternion) FUNCTION quat_from_complex(c) RESULT(r) COMPLEX c r%x = REAL(c) r%y = AIMAG(c) r%z = 0 r%a = 0 END FUNCTION ... COMPLEX c TYPE(quaternion) q q = quaternion(3.14159265) ! Structure constructor, value (~pi,0,0,0). q = quaternion(jx=1) ! Structure constructor, value (0,0,1,0). q = quaternion(c) ! "Constructor" function quat_from_complex.
Also, if the type is an extended type an ancestor component name can be used to provide a value for all those inherited components at once.
These extensions mean that even if a type has a private component, you can use the structure constructor if
CHARACTER(LEN=:),POINTER :: chThe length of a deferred-length pointer (or allocatable variable) is determined when it is allocated (see next section) or pointer-associated; for example
CHARACTER,TARGET :: t1*3,t2*27 CHARACTER(:),POINTER :: p p => t1 PRINT *,LEN(p) p => t2 PRINT *,LEN(p)will first print 3 and then 27. It is not permitted to ask for the
LEN
of a disassociated pointer that
has deferred length.
Note that deferred length is most useful in conjunction with the new features of typed allocation, sourced allocation, scalar allocatables and automatic reallocation.
ALLOCATE
and DEALLOCATE
statements now accept the
ERRMSG=
specifier.
This specifier takes a scalar default character variable, which in the event of
an allocation or deallocation error being detected will be assigned an
explanatory message.
If no error occurs the variable is left unchanged.
Note that this is useless unless the STAT=
specifier is also used, as
otherwise the program will be terminated on error anyway.
For example,
ALLOCATE(w(n),STAT=ierror,ERRMSG=message) IF (ierror/=0) THEN PRINT *,'Error allocating W: ',TRIM(message) RETURN END IF
MODULE m REAL,PARAMETER :: e = EXP(1.0) END
RECURSIVE
attribute).
For example
PURE INTEGER FUNCTION factorial(n) RESULT(r) INTEGER,INTENT(IN) :: n IF (n>1) THEN r = n*factorial(n-1) ELSE r = 1 END IF END FUNCTIONcan now be used in a specification expression. Note that a specification function must not invoke the procedure that invoked it.
COMMAND_ARGUMENT_COUNT
, GET_COMMAND
and GET_COMMAND_ARGUMENT
have been added.
These duplicate functionality previously only available via the procedures
IARGC
and GETARG
from the F90_UNIX_ENV
module.
INTEGER FUNCTION command_argument_count()Returns the number of command-line arguments. Unlike
IARGC
in the F90_UNIX_ENV
module,
this returns 0 even if the command name cannot be retrieved.
SUBROUTINE get_command(command,length,status) CHARACTER(*),INTENT(OUT),OPTIONAL :: command INTEGER,INTENT(OUT),OPTIONAL :: length,statusAccesses the command line which invoked the program. This is formed by concatenating the command name and the arguments separated by blanks. This might differ from the command the user actually typed, and should be avoided (use
GET_COMMAND_ARGUMENT
instead).
If COMMAND
is present, it receives the command (blank-padded
or truncated as appropriate).
If LENGTH
is present, it receives the length of the command.
If STATUS
is present, it is set to −1 if COMMAND
is too short to
hold the whole command, a positive number if the command cannot be retrieved,
and zero otherwise.
SUBROUTINE get_command_argument(number,value,length,status) INTEGER,INTENT(IN) :: number CHARACTER(*),INTENT(OUT),OPTIONAL :: value INTEGER,INTENT(OUT),OPTIONAL :: length,statusAccesses command-line argument number
NUMBER
, where argument zero is
the program name.
If VALUE
is present, it receives the argument text (blank-padded or
truncated as appropriate if the length of the argument differs from that of
VALUE
).
If LENGTH
is present, it receives the length of the argument.
If STATUS
is present, it is set to zero for success, −1 if VALUE
is too short, and a positive number if an error occurs.
Note that it is an error for NUMBER
to be less than zero or greater
than the number of arguments (returned by COMMAND_ARGUMENT_COUNT
).
GET_ENVIRONMENT_VARIABLE
has been added.
This duplicates the functionality previously only available via the procedure
GETENV
in the F90_UNIX_ENV
module.
SUBROUTINE get_environment_variable(name,value,length,status,trim_name) CHARACTER(*),INTENT(IN) :: name CHARACTER(*),INTENT(OUT),OPTIONAL :: value INTEGER,INTENT(OUT),OPTIONAL :: length,status LOGICAL,INTENT(IN),OPTIONAL :: trim_name ENDAccesses the environment variable named by
NAME
; trailing blanks in
NAME
are ignored unless TRIM_NAME
is present with the value
.FALSE.
.
If VALUE
is present, it receives the text value of the variable
(blank-padded or truncated as appropriate if the length of the value differs
from that of VALUE
).
If LENGTH
is present, it receives the length of the value.
If STATUS
is present, it is assigned the value 1 if the environment
variable does not exist, −1 if VALUE
is too short, and zero for success.
Other positive values might be assigned for unusual error conditions.
SELECTED_CHAR_KIND
has been added.
At this time the only character set supported is 'ASCII'
.
CHARACTER
scalar actual argument may now be passed to a routine which
expects to receive a CHARACTER
array, provided the array is
explicit-shape or assumed-size (i.e. not assumed-shape, allocatable, or
pointer).
This is useful for C interoperability.
MAXLOC
and MINLOC
intrinsic functions now return zeroes for
empty set locations, as required by Fortran 2003 (Fortran 95 left this result
processor-dependent).
VALUE
attribute may be specified by the VALUE
statement or
with the VALUE
keyword in a type declaration statement.
The syntax of the VALUE
statement is:
VALUE
[ ::
] name [ ,
name ] ...
The VALUE
attribute may only be specified for a scalar dummy argument;
if the dummy argument is of type CHARACTER
, its character length must be
constant and equal to one.
Procedures with a VALUE
dummy argument must have an explicit interface.
VALUE
attribute is “passed by value”;
this means that a local copy is made of the argument on entry to the routine
and so modifications to the dummy argument do not affect the associated actual
argument and vice versa.
A VALUE
dummy argument may be INTENT(IN)
but cannot be
INTENT(INOUT)
or INTENT(OUT)
.
PROGRAM value_example INTEGER :: i = 3 CALL s(i) PRINT *,i ! This will print the value 3 CONTAINS SUBROUTINE s(j) INTEGER,VALUE :: j j = j + 1 ! This changes the local J without affecting the actual argument PRINT *,j ! This will print the value 4 END SUBROUTINE ENDThis example is not intended to be particularly useful, just to illustrate the functionality.
volatile
’
type qualifier; essentially it disables optimisation for access to that
variable.
REAL,PARAMETER :: minusone = -1.0 COMPLEX,PARAMETER :: c = (0,minusone)This is not particularly useful, since the same effect can be achieved by using the
CMPLX
intrinsic function.
ASSOCIATE
construct [5.2]ASSOCIATE
construct establishes a temporary association between the
“associate names” and the specified variables or values, during
execution of a block.
Its syntax is
ASSOCIATE (
association [ ,
association ]... )
block
END ASSOCIATE
name =>
expression
name =>
variable
name
=>
name’.
The scope of each “associate name” is the block of the
ASSOCIATE
construct.
An associate name is never allocatable or a pointer, but otherwise has the same
attributes as the variable or expression (and it has the
TARGET
attribute if the variable or expression is a pointer).
If it is being associated with an expression, the expression is evaluated on
execution of the ASSOCIATE
statement and its value does not change
during execution of the block — in this case, the associate name is
not permitted to appear on the left-hand-side of an assignment or any other
context which might change its value.
If it is being associated with a variable, the associate name can be treated
as a variable.
The type of the associate name is that of the expression or variable with which it is associated. For example, in
ASSOCIATE(zoom=>NINT(SQRT(a+b)), alt=>state%mapval(:,i)%altitude) alt%x = alt%x*zoom alt%y = alt%y*zoom END ASSOCIATE
ALT
is associated with a variable and therefore can be modified whereas
ZOOM
cannot. The expression for ZOOM
is of type INTEGER
and therefore ZOOM
is also of type INTEGER
.
DATA
statements, but in Fortran
2003 these are now allowed to be arguments of the intrinsic functions
CMPLX
, DBLE
, INT
and REAL
.
The interpretation is processor-dependent, but the intent is that this
specifies the internal representation of the complex or real value.
The NAG Fortran compiler requires these constants to have the correct length
for the specified kind of complex or real, viz 32 or 64 bits as appropriate.
For example, on a machine where default REAL is IEEE single precision,
REAL(z"41280000")has the value
10.5
.
The default character set is now required to include lowercase letters and all the 7-bit ASCII printable characters.
The ENCODING=
specifer for the OPEN
and INQUIRE
statements
is described in the input/output section.
A new intrinsic function SELECTED_CHAR_KIND(NAME)
has been added:
this returns the character kind for the named character set, or −1 if there
is no kind for that character set.
Standard character set names are 'DEFAULT'
for the default character
kind, 'ASCII'
for the 7-bit ASCII character set and 'ISO_10646'
for the UCS-4 (32-bit Unicode) character set.
The name is not case-sensitive.
Note that although the method of requesting UCS-4 characters is standardised,
the compiler is not required to support them (in which case −1 will be
returned); the NAG Fortran Compiler supports UCS-4 in release 5.3
(as well as UCS-2 and JIS X 0213).
Assignment of a character value of one kind to a character value of a different kind is permitted if each kind is one of default character, ASCII character, or UCS-4 character. Assignment to and from a UCS-4 character variable preserves the original value.
Internal file input/output to variables of UCS-4 character kind is allowed (if the kind exists), including numeric conversions (e.g. the E edit descriptor), and conversions from/to default character and ASCII character. Similarly, writing default character, ASCII character and UCS-4 character values to a UTF-8 file and reading them back is permitted and preserves the value.
Finally, the intrinsic function IACHAR
(for converting characters to the
ASCII character set) accepts characters of any kind (in Fortran 95 it only
accepted default kind).
KIND
argument at the end of the argument
list, to specify the kind of integer they return.
The functions are: COUNT
, INDEX
, LBOUND
, LEN
,
LEN_TRIM
, SCAN
, SHAPE
, SIZE
, UBOUND
and
VERIFY
.
DATE_AND_TIME
no longer requires the
three character arguments (DATE
, TIME
and ZONE
) to have
a minimum length: if the actual argument is too small, it merely truncates the
value assigned.
The intrinsic functions IACHAR
and ICHAR
now accept an optional
KIND
argument to specify the kind of integer to which to convert the
character value. This serves no useful purpose since there are no character
sets with characters bigger than 32 bits.
The intrinsic functions MAX
, MAXLOC
, MAXVAL
, MIN
,
MINLOC
and MINVAL
all now accept character values; the comparison
used is the native (.LT.
) one, not the ASCII (LLT
) one.
The intrinsic subroutine SYSTEM_CLOCK
now accepts a COUNT_RATE
argument of type real; this is to handle systems whose clock ticks are not an
integral divisor of 1 second.