Chapter 1. Fortran Syntax

This chapter contains a complete description of the Fortran syntax. “Syntax Form” describes the format of the syntax. “Syntax Rules and Constraints”, contains the complete syntax and constraints as they appear in the Fortran standard. A high-level summary of the syntax appears in the Fortran Language Reference Manual, Volume 1.

Syntax Form

The syntax of Fortran programs is described using a variant of the Backus-Naur Form (BNF).

Syntax Rules Expressed in BNF

The BNF syntax rules are expressed as a definition. The metalanguage class being defined is first, followed by the symbol is, and finally the syntax definition, as in the following example:

goto_stmt

is

GO TO label

The term goto_stmt represents the GO TO statement; such terms are called nonterminal symbols or simply nonterminals. The syntax rule defines goto_stmt as GO TO label, which describes the form of the GO TO statement. The description of the GO TO statement is not complete until the definition of label is specified; label is also a nonterminal symbol. A further search for label in the BNF will result in a specification of label and thereby provide the complete statement definition. A terminal part of a syntax rule does not need further definition. For example, GO TO is a terminal and is a required part of the statement form.

In many cases, you can derive information about the metalanguage class from part of the descriptive term. The part can be a complete word, such as _list, or a common abbreviation. Some abbreviations used consistently in metalanguage classes are listed in Table 1-1.

Table 1-1. Syntax metalanguage abbreviations

Abbreviation

Term

arg

Argument

attr

Attribute

char

Character

decl

Declaration

def

Definition

desc

Descriptor

expr

Expression

int

Integer

op

Operator

spec

Specifier or specification

stmt

Statement

For example, all class definitions that end with _stmt might be used to generate a complete list of the statements in Fortran.

Definition Syntax Symbol: Is

As the following example shows, the symbol is separates the syntax class name from its definition:

goto_stmt

is

GO TO label

power_op

is

**


Alternative Syntax Symbol: Or

The symbol or indicates an alternative definition for the syntactic class being defined. The following example shows that add_op, the add operator, can be either plus or minus.

add_op

is

+

 

or

-


Optional Symbol: []

Some syntactic definitions contain optional items, which are enclosed in brackets. The term sign is optional in the following example:

signed_int_literal_constant

is

[sign]int_literal_constant

The fact that sign is optional indicates, for example, that both 75 and +75 are signed_int_literal_constants.

Symbol for Repeated Items: [] . . .

Enclosing an item in brackets followed by an ellipsis indicates that the item can occur 0 or more times. In the following example, the term digit is repeated as many times as required to define the int_literal_constant:

int_literal_constant

is

digit[digit] ...

For example, there are five digits in the integer literal constant 94024.

Syntax Rule Continuation

If a rule does not fit on one line, the convention is to indent the second line of the syntax. This is shown in the following example:

allocatable_stmt

is

ALLOCATABLE [ :: ]
array_name[( deferred_shape_spec_list  )]
[, array_name[( deferred_shape_spec_list )]]...


Assumed Syntax Rules

In order to minimize the number of syntax rules and still convey an appropriate meaning, some portions of the BNF metaterms have assumed meanings. In the following example, xyz represents any BNF phrase:

xyz_list

means

xyz[, xyz] ...

xyz_name

is

a name

scalar_xyz

is

an xyz that is a scalar


Example BNF Syntax

Consider the following example:

read_stmt

is

READ ( io_control_spec_list ) [input_item_list]

 

or

READ format[, input_item_list]

format

is

default_char_expr

 

or

label

 

or

*

 

or

scalar_default_int_variable

In this example, there are two alternatives to the READ statement. The first uses an input/output (I/O) control specification list; the second is a formatted READ statement where the unit is processor dependent. Both alternatives have an optional input item list, indicated by []. The syntax class format (a nonterminal) is further defined as either a default character expression containing the format specifications, or a statement label referring to a separate FORMAT statement that contains the format specifications, or an asterisk (*) indicating that the READ statement is list-directed, or a scalar default integer variable whose value specifies the label of a FORMAT statement. In the standard, the last alternative is printed in a smaller font because it is an obsolescent feature that may be removed in a later revision of the standard, including the next revision; this convention is not used in this manual.

There are other nonterminal symbols in the description of the READ statement and further BNF rules need to be examined to determine the complete description of the READ statement.

Constraints

The BNF forms do not provide a complete description of the syntax; additional constraints are described with text. The BNF rules and the constraints both describe the syntax of Fortran. Constraints are restrictions to the syntax rules that limit the form of the statement described. If present, constraints appear following a syntax rule.

Identifying Numbers

In the text of the standard, each BNF rule is given an identifying number, R201 for example. The numbering of the rules in the following subsections matches the numbering of the rules in the standard.

BNF rules are also used to describe extensions. In the following BNF description, for example, "EXT" in the leftmost column indicates that the CF90 and MIPSpro 7 Fortran 90 compilers also allow unit_name to be used as an io_unit:

R901

io_unit

is

external_file_unit

 

 

or

*

 

 

or

internal_file_unit

EXT

 

or

unit_name


Syntax Rules and Constraints

Each of the following sections contains the syntax rules and constraints from a section of the Fortran standard. The following sections use an underscore, rather than a hyphen, as a separator; this differs from the Fortran standard. The rules in the following sections have been amended to include BNF for the CF90 and MIPSpro 7 Fortran 90 compiler extensions to the Fortran standard, but the constraints have not been modified to reflect the extensions.

Introduction

There are no syntax rules described in section 1, "Introduction," of the Fortran 95 standard.

Fortran Terms and Concepts

The following syntax rules are described in section 2, "Fortran terms and concepts," of the Fortran 95 standard.

R201

executable_program

is

program_unit[program_unit] ...

R202

program_unit

is

main_program

  

or

external_subprogram

  

or

module

  

or

block_data

R1101

main_program

is

[program_stmt]
[specification_part]
[execution_part]
[internal_subprogram_part]
end_program_stmt

Constraint: An execution_part must not contain an end_function_stmt, end_program_stmt, or end_subroutine_stmt.

R203

external_subprogram

is

function_subprogram

  

or

subroutine_subprogram

R1215

function_subprogram

is

function_stmt
[specification_part]
[execution_part]
[internal_subprogram_part]
end_function_stmt

R1219

subroutine_subprogram

is

subroutine_stmt
[specification_part]
[execution_part]
[internal_subprogram_part]
end_subroutine_stmt

R1104

module

is

module_stmt
[specification_part]
[module_subprogram_part]
end_module_stmt

R1112

block_data

is

block_data_stmt
[specification_part]
end_block_data_stmt

R204

specification_part

is

[use_stmt] ...
[implicit_part]
[declaration_construct] ...

R205

implicit_part

is

[implicit_part_stmt] ...
implicit_stmt

R206

implicit_part_stmt

is

implicit_stmt

  

or

parameter_stmt

  

or

format_stmt

  

or

entry_stmt

R207

declaration_construct

is

derived_type_def

  

or

interface_block

  

or

type_declaration_stmt

  

or

specification_stmt

  

or

parameter_stmt

  

or

format_stmt

  

or

entry_stmt

  

or

stmt_function_stmt

R208

execution_part

is

executable_construct
[execution_part_construct] ...

R209

execution_part_construct

is

executable_construct

  

or

format_stmt

  

or

data_stmt

  

or

entry_stmt

R210

internal_subprogram_part

is

contains_stmt
internal_subprogram
[internal_subprogram]...

R211

internal_subprogram

is

function_subprogram

  

or

subroutine_subprogram

R212

module_subprogram_part

is

contains_stmt
module_subprogram
[module_subprogram] ...

R213

module_subprogram

is

function_subprogram

  

or

subroutine_subprogram

R214

specification_stmt

is

access_stmt

  

or

allocatable_stmt

EXT

 

or

automatic_stmt

  

or

common_stmt

  

or

data_stmt

  

or

dimension_stmt

  

or

equivalence_stmt

  

or

external_stmt

  

or

intent_stmt

  

or

intrinsic_stmt

  

or

namelist_stmt

  

or

optional_stmt

  

or

pointer_stmt

  

or

save_stmt

  

or

target_stmt

EXT

 

or

volatile_stmt

R215

executable_construct

is

action_stmt

  

or

case_construct

  

or

do_construct

  

or

if_construct

  

or

forall_construct

  

or

where_construct

R216

action_stmt

is

allocate_stmt

OBS

 

or

arithmetic_if_stmt

EXT

 

or

assign_stmt

EXT

 

or

assigned_goto_stmt

 

 

or

assignment_stmt

 

 

or

backspace_stmt

EXT

 

or

buffer_in_stmt

EXT

 

or

buffer_out_stmt

  

or

call_stmt

  

or

close_stmt

OBS

 

or

computed_goto_stmt

  

or

continue_stmt

  

or

cycle_stmt

  

or

deallocate_stmt

  

or

endfile_stmt

  

or

end_function_stmt

  

or

end_program_stmt

  

or

end_subroutine_stmt

  

or

exit_stmt

  

or

forall_stmt

  

or

goto_stmt

  

or

if_stmt

  

or

inquire_stmt

  

or

nullify_stmt

  

or

open_stmt

EXT

 

or

pause_stmt

  

or

pointer_assignment_stmt

  

or

print_stmt

  

or

read_stmt

  

or

return_stmt

  

or

rewind_stmt

  

or

stop_stmt

  

or

where_stmt

  

or

write_stmt


Characters, Lexical Tokens, and Source Form

The following syntax rules are described in section 3, "Characters, lexical tokens, and source form," of the Fortran 95 standard.

R301

character

is

alphanumeric_character

  

or

special_character

R302

alphanumeric_character

is

letter

 

 

or

digit

 

 

or

underscore

EXT

 

or

currency_symbol

EXT

 

or

at_sign



Note:: The MIPSpro 7 Fortran 90 compiler does not support the at_sign (@).


R303

underscore

is

_

EXT

currency_symbol

is

$

EXT

at_sign

is

@

R304

name

is

letter[alphanumeric_character] ...

Constraint: The maximum length of a name is 31 characters.

R305

constant

is

literal_constant

  

or

named_constant

R306

literal_constant

is

int_literal_constant

  

or

real_literal_constant

  

or

complex_literal_constant

  

or

logical_literal_constant

  

or

char_literal_constant

  

or

boz_literal_constant

R307

named_constant

is

name

R308

int_constant

is

constant

Constraint: int_constant must be of type integer.

R309

char_constant

is

constant

Constraint: char_constant must be of type character.

R310

intrinsic_operator

is

power_op

  

or

mult_op

  

or

add_op

  

or

concat_op

  

or

rel_op

  

or

not_op

  

or

and_op

  

or

or_op

  

or

equiv_op

R708

power_op

is

**

R709

mult_op

is

*

  

or

/

R710

add_op

is

+

  

or

-

R712

concat_op

is

//

R714

rel_op

is

.EQ.

 

 

or

.NE.

 

 

or

.LT.

 

 

or

.LE.

 

 

or

.GT.

 

 

or

.GE.

EXT

 

or

.LG.

 

 

or

==

 

 

or

/=

 

 

or

<

 

 

or

<=

 

 

or

>

 

 

or

>=

EXT

 

or

<>

R719

not_op

is

.NOT.

EXT

 

or

.N.

R720

and_op

is

.AND.

EXT

 

or

.A.

R721

or_op

is

.OR.

EXT

 

or

.O.

R722

equiv_op

is

.EQV.

 

 

or

.NEQV.

EXT

exclusive_disjunct_op

is

.XOR.

EXT

 

or

.X.

R311

defined_operator

is

defined_unary_op

  

or

defined_binary_op

  

or

extended_intrinsic

R704

defined_unary_op

is

. letter[letter] ... .

R724

defined_binary_op

is

. letter[letter] ... .

R312

extended_intrinsic_op

is

intrinsic_operator

Constraint: A defined_unary_op and a defined_binary_op must not contain more than 31 letters and must not be the same as any intrinsic_operator or logical_literal_constant.

R313

label

is

digit[digit[digit[digit[digit]]]]

Constraint: At least one digit in a label must be nonzero.

Intrinsic and Derived Data Types

The following syntax rules are described in section 4, "Intrinsic and derived data types," of the Fortran 95 standard.

R401

signed_digit_string

is

[sign]digit_string

R402

digit_string

is

digit[digit] ...

R403

signed_int_literal_constant

is

[sign]int_literal_constant

R404

int_literal_constant

is

digit_string[_ kind_param]

R405

kind_param

is

digit_string

  

or

scalar_int_constant_name

Constraint: The value of kind_param must be nonnegative.

Constraint: The value of kind_param must specify a representation method that exists on the processor.

R406

sign

is

+

  

or

-

R407

boz_literal_constant

is

binary_constant

  

or

octal_constant

  

or

hex_constant

Constraint: A boz_literal_constant may appear only in a DATA statement.

R408

binary_constant

is

B ' digit[digit] ... '

  

or

B " digit[digit] ... "

Constraint: digit must have one of the values 0 or 1.

R409

octal_constant

is

O ' digit[digit] ... '

  

or

O " digit[digit] ... "

Constraint: digit must have one of the values 0 through 7.

R410

hex_constant

is

Z ' hex_digit[hex_digit]... '

 

 

or

Z " hex_digit[hex_digit] ... "

R411

hex_digit

is

digit

 

 

or

A

 

 

or

B

 

 

or

C

 

 

or

D

 

 

or

E

 

 

or

F

R412

signed_real_literal_constant

is

[sign]real_literal_constant

R413

real_literal_constant

is

significand[exponent_letter exponent][_ kind_param]

 

 

or

digit_string exponent_letter exponent[_ kind_param]

R414

significand

is

digit_string . [digit_string]

 

 

or

. digit_string

R415

exponent_letter

is

E

 

 

or

D

EXT

 

or

Q

R416

exponent

is

signed_digit_string

Constraint: If both kind_param and exponent_letter are present, exponent_letter must be E.

Constraint: The value of kind_param must specify an approximation method that exists on the processor.

R417

complex_literal_constant

is

( real_part , imag_part )

R418

real_part

is

signed_int_literal_constant

  

or

signed_real_literal_constant

R419

imag_part

is

signed_int_literal_constant

  

or

signed_real_literal_constant

R420

char_literal_constant

is

[kind_param _] ' [ASCII_char] ... '

  

or

[kind_param _] " [ASCII_char] ... "

Constraint: The value of kind_param must specify a representation method that exists on the processor.

R421

logical_literal_constant

is

.TRUE. [_ kind_param]

  

or

.FALSE. [_ kind_param]

Constraint: The value of kind_param must specify a representation method that exists on the processor.

R422

derived_type_def

is

derived_type_stmt
[private_sequence_stmt] ...
component_def_stmt
[component_def_stmt] ...
 end_type_stmt

R423

derived_type_stmt

is

TYPE [[, access_spec] :: ]type_name

R424

private_sequence_stmt

is

PRIVATE

  

or

SEQUENCE

Constraint: The same private_sequence_stmt must not appear more than once in a given derived_type_def.

Constraint: If SEQUENCE is present, all derived types specified in component definitions must be sequence types.

Constraint: An access_spec or a PRIVATE statement within the definition is permitted only if the type definition is within the specification part of a module.

Constraint: A derived type type_name must not be the same as the name of any intrinsic type nor the same as any other accessible derived type type_name.

R425

component_def_stmt

is

type_spec[[, component_attr_spec_list] :: ]component_decl_list

R426

component_attr_spec

is

POINTER

  

or

DIMENSION (component_array_spec)

R427

component_array_spec

is

explicit_shape_spec_list

  

or

deferred_shape_spec_list

Constraint: If a component of a derived type is of a type declared to be private, either the derived type definition must contain the PRIVATE statement or the derived type must be private.

Constraint: No component_attr_spec can appear more than once in a given component_def_stmt.

Constraint: If the POINTER attribute is not specified for a component, a type_spec in the component_def_stmt must specify an intrinsic type or a previously defined derived type.

Constraint: If the POINTER attribute is specified for a component, a type_spec in the component_def_stmt must specify an intrinsic type or any accessible derived type including the type being defined.

Constraint: If the POINTER attribute is not specified, each component_array_spec must be an explicit_shape_spec_list.

Constraint: If the POINTER attribute is specified, each component_array_spec must be a deferred_shape_spec_list.

R428

component_decl

is

component_name[ (component_array_spec) ][ * char_length]
component_initialization

R429

component_initialization

is

= initialization_expr

  

or

=> NULL()

Constraint: The *char_length option is permitted only if the type specified is character.

Constraint: The character length specified by a char_length in a component_decl or the char_selector in a type_spec must be a constant specification expression.

Constraint: Each bound in the explicit_shape_spec must be a constant specification expression.

Constraint: If component_initialization appears, a double colon separator (::) must appear before the component_decl_list.

Constraint: If => appears in component_initialization, the POINTER attribute must appear in the component_attr_spec_list. If = appears in component_initialization, the POINTER attribute must not appear in the component_attr_spec_list.

R430

end_type_stmt

is

END TYPE [type_name]

Constraint: If END TYPE is followed by a type_name, the type_name must be the same as that in the corresponding derived_type_stmt.

R431

structure_constructor

is

type_name ( expr_list )

R432

array_constructor

is

(/ ac_value_list /)

R433

ac_value

is

expr

  

or

ac_implied_do

R434

ac_implied_do

is

( ac_value_list , ac_implied_do_control )

R435

ac_implied_do_control

is

ac_do_variable = scalar_int_expr, scalar_int_expr[, scalar_int_expr]

R436

ac_do_variable

is

scalar_int_variable

Constraint: ac_do_variable must be a named variable.

Constraint: Each ac_value expression in the array_constructor must have the same type and kind type parameters.

Data Object Declarations and Specifications

The following syntax rules are described in section 5, "Data object declarations and specifications," of the Fortran 95 standard.

R501

type_declaration_stmt

is

type_spec[[, attr_spec] ... :: ]entity_decl_list

R502

type_spec

is

INTEGER [kind_selector]

EXT

 

or

INTEGER* length_value

 

 

or

REAL [kind_selector]

EXT

 

or

REAL* length_value

 

 

or

DOUBLE PRECISION

EXT

 

or

DOUBLE PRECISION* length_value

 

 

or

COMPLEX [kind_selector]

EXT

 

or

COMPLEX* length_value

 

 

or

CHARACTER [char_selector]

 

 

or

LOGICAL [kind_selector]

EXT

 

or

LOGICAL* length_value

 

 

or

TYPE ( type_name )

EXT

 

or

POINTER ( pointer_name, pointee_name[( array_spec )] )

   

[, (pointer_name, pointee_name[( array_spec )] )] ...

R503

attr_spec

is

PARAMETER

 

 

or

access_spec

 

 

or

ALLOCATABLE

EXT

 

or

AUTOMATIC 

  

or

DIMENSION ( array_spec )

  

or

EXTERNAL

  

or

INTENT ( intent_spec )

  

or

INTRINSIC

  

or

OPTIONAL

  

or

POINTER

  

or

SAVE

  

or

TARGET

EXT

 

or

VOLATILE

R504

entity_decl

is

object_name[( array_spec )][ * char_length][ = initialization_expr]

  

or

function_name[ * char_length]

R505

initialization

is

= initialization_expr

  

or

=> NULL()

R506

kind_selector

is

([KIND = ]scalar_int_initialization_expr )

Constraint: The same attr_spec must not appear more than once in a given type_declaration_stmt.

Constraint: The function_name must be the name of an external function, an intrinsic function, a function dummy procedure, or a statement function.

Constraint: The initialization_expr must appear if the statement contains a PARAMETER attribute.

Constraint: If initialization_expr appears, a double colon separator (::) must appear before the entity_decl_list.

Constraint: The initialization_expr must not appear if object_name is a dummy argument, a function result, or an object in a named common block unless the type declaration is in a block data program unit, an object in blank common, an allocatable array, an external name, an intrinsic name, or an automatic object.

Constraint: The *char_length option is permitted only if the type specified is character.

Constraint: The ALLOCATABLE attribute may be used only when declaring an array that is not a dummy argument or a function result.

Constraint: An array declared with a POINTER or an ALLOCATABLE attribute must be specified with an array_spec that is a deferred_shape_spec_list.

Constraint: An array_spec for an object_name that is a function result that does not have the POINTER attribute must be an explicit_shape_spec_list.

Constraint: An array_spec for an object_name that is a function result that has the POINTER attribute must be a deferred_shape_spec_list.

Constraint: If the POINTER attribute is specified, the TARGET, INTENT, EXTERNAL, or INTRINSIC attribute must not be specified.

Constraint: If the TARGET attribute is specified, the POINTER, EXTERNAL, INTRINSIC, or PARAMETER attribute must not be specified.

Constraint: The PARAMETER attribute must not be specified for dummy arguments, pointers, allocatable arrays, functions, or objects in a common block.

Constraint: The INTENT and OPTIONAL attributes may be specified only for dummy arguments.

Constraint: An entity must not have the PUBLIC attribute if its type has the PRIVATE attribute.

Constraint: The SAVE attribute must not be specified for an object that is in a common block, a dummy argument, a procedure, a function result, an automatic data object, or an object with the PARAMETER attribute.

Constraint: An entity must not have the EXTERNAL attribute if it has the INTRINSIC attribute.

Constraint: An entity in an entity_decl_list must not have the EXTERNAL or INTRINSIC attribute specified unless it is a function.

Constraint: If => appears in initialization, the object must have the POINTER attribute. If = appears in initialization, the object must not have the POINTER attribute.

Constraint: An array must not have both the ALLOCATABLE attribute and the POINTER attribute.

Constraint: An entity must not be given explicitly any attribute more than once in a scoping unit.

Constraint: The value of scalar_int_initialization_expr must be nonnegative and must specify a representation method that exists on the processor.

R507

char_selector

is

length_selector

  

or

( LEN = char_len_param_value, KIND = scalar_int_initialization_expr )

  

or

( char_len_param_value, [ KIND = ]scalar_int_initialization_expr )

  

or

( KIND = scalar_int_initialization_expr
[, LEN = char_len_param_value])

R508

length_selector

is

([ LEN = ]char_len_param_value )

OBS

 

or

* char_length[ , ]

R509

char_length

is

( char_len_param_value )

  

or

scalar_int_literal_constant

Obsolescent Constraint: The optional comma in a length_selector is permitted only in a type_spec in a type_declaration_stmt.

Obsolescent Constraint: The optional comma in a length_selector is permitted only if no double colon separator appears in the type_declaration_stmt.

Constraint: The value of scalar_int_initialization_expr must be nonnegative and must specify a representation method that exists on the processor.

Constraint: The scalar_int_literal_constant must not include a kind_param.

R510

char_len_param_value

is

specification_expr

  

or

*

Obsolescent Constraint: A function name must not be declared with a *char_len_param_value unless it is the name of an external function or the name of a dummy function.

Constraint: A function name declared with a *char_len_param_value must not be array-valued, pointer-valued, pure, or recursive.

R511

access_spec

is

PUBLIC

  

or

PRIVATE

Constraint: An access_spec attribute may appear only in the specification part of a module.

R512

intent_spec

is

IN

  

or

OUT

  

or

INOUT

Constraint: The INTENT attribute must not be specified for a dummy argument that is a dummy procedure or a dummy pointer.

Constraint: A dummy argument with the INTENT(IN) attribute, or a subobject of such a dummy argument, must not appear as any of the following:

  • The variable of an assignment_stmt

  • The pointer_object of a pointer_assignment_stmt

  • A DO-variable or implied DO-variable

  • An input_item in a read_stmt

  • A variable_name in a namelist_stmt if the name_list_group_name appears in an NML= specifier in a read_stmt

  • An internal_file_unit in a write_stmt

  • An IOSTAT= or SIZE= specifier in an I/O statement

  • A definable variable in an INQUIRE statement

  • A stat_variable or allocate_object in an allocate_stmt or a deallocate_stmt

  • An actual argument in a reference to a procedure with an explicit interface when the associated dummy argument has the INTENT(OUT) or INTENT(INOUT) attribute

R513

array_spec

is

explicit_shape_spec_list

  

or

assumed_shape_spec_list

  

or

deferred_shape_spec_list

  

or

assumed_size_spec

Constraint: The maximum rank is seven.

R514

explicit_shape_spec

is

[lower_bound : ]upper_bound

R515

lower_bound

is

specification_expr

R516

upper_bound

is

specification_expr

Constraint: An explicit-shape array whose bounds depend on the values of nonconstant expressions must be a dummy argument, a function result, or an automatic array of a procedure.

R517

assumed_shape_spec

is

[lower_bound] :

R518

deferred_shape_spec

is

:

R519

assumed_size_spec

is

[explicit_shape_spec_list, ][lower_bound : ] *

Constraint: The function name of an array-valued function must not be declared as an assumed-size array.

Constraint: An assumed-size array with INTENT(OUT) must not be of a type for which default initialization is specified.

R520

intent_stmt

is

INTENT ( intent_spec ) [ :: ]dummy_arg_name_list

Constraint: An intent_stmt may appear only in the specification_part of a subprogram or an interface body.

Constraint: dummy_arg_name must not be the name of a dummy procedure or a dummy pointer.

R521

optional_stmt

is

OPTIONAL [ :: ]dummy_arg_name_list

Constraint: An optional_stmt can occur only in the specification_part of a subprogram or an interface body.

R522

access_stmt

is

access_spec[[ :: ]access_id_list]

R523

access_id

is

use_name

  

or

generic_spec

Constraint: An access_stmt can appear only in the specification_part of a module. Only one accessibility statement with an omitted access_id_list is permitted in the specification_part of a module.

Constraint: Each use_name must be the name of a named variable, procedure, derived type, named constant, or namelist group.

Constraint: A module procedure that has a dummy argument or function result of a type that has PRIVATE accessibility must have PRIVATE accessibility and must not have a generic identifier that has PUBLIC accessibility.

R524

save_stmt

is

SAVE [[ :: ]saved_entity_list]

R525

saved_entity

is

object_name

  

or

/ common_block_name /

Constraint: An object_name must not be the name of an object in a common block, a dummy argument name, a procedure name, a function result name, an automatic data object name, or the name of an object with the PARAMETER attribute.

Constraint: If a SAVE statement with an omitted saved entity list occurs in a scoping unit, no other explicit occurrence of the SAVE attribute or SAVE statement is permitted in the same scoping unit.

R526

dimension_stmt

is

DIMENSION [ :: ]array_name(array_spec)
[, array_name(array_spec)] ...

R527

allocatable_stmt

is

ALLOCATABLE [ :: ]array_name[(deferred_shape_spec_list)]
[, array_name[(deferred_shape_spec_list)]] ...

Constraint: The array_name must not be a dummy argument or function result.

Constraint: If the DIMENSION attribute for an array_name is specified elsewhere in the scoping unit, the array_spec must be a deferred_shape_spec_list.

R528

pointer_stmt

is

POINTER [ :: ]object_name[ (deferred_shape_spec_list) ]
[, object_name[ (deferred_shape_spec_list) ]] ...

Constraint: The INTENT attribute must not be specified for an object_name.

Constraint: If the DIMENSION attribute for an object_name is specified elsewhere in the scoping unit, the array_spec must be a deferred_shape_spec_list.

Constraint: The PARAMETER attribute must not be specified for an object_name.

R529

target_stmt

is

TARGET [ :: ]object_name[ (array_spec) ]
[, object_name[ (array_spec) ]] ...

Constraint: The PARAMETER attribute must not be specified for an object_name.

R532

data_stmt

is

DATA data_stmt_set[[ , ]data_stmt_set] ...

R533

data_stmt_set

is

data_stmt_object_list / data_stmt_value_list /
[[ , ]data_stmt_object_list / data_stmt_value_list / ] ...

R534

data_stmt_object

is

variable

  

or

data_implied_do

R535

data_implied_do

is

( data_i_do_object_list,
data_i_do_variable = scalar_int_expr,
scalar_int_expr[ , scalar_int_expr] )

R536

data_i_do_object

is

array_element

  

or

scalar_structure_component

  

or

data_implied_do

R538

data_stmt_value

is

[data_stmt_repeat * ]data_stmt_constant

R539

data_stmt_repeat

is

scalar_int_constant

 

 

or

scalar_int_constant_subobject

R540

data_stmt_constant

is

scalar_constant

 

 

or

scalar_constant_subobject

 

 

or

signed_int_literal_constant

 

 

or

signed_real_literal_constant

 

 

or

structure_constructor

 

 

or

NULL()

 

 

or

boz_literal_constant

EXT

 

or

typeless_constant

A data_i_do_variable must be a named variable.

Constraint: The array_element must not have a constant parent.

Constraint: The scalar_structure_component must not have a constant parent.

Constraint: In a scalar_int_constant_subobject that is a data_stmt_repeat, any subscript must be an initialization expression.

Constraint: In a scalar_constant_subobject that is a data_stmt_constant, any subscript, substring starting point, or substring ending point must be an initialization expression.

Constraint: If a DATA statement constant value is a named constant or a structure constructor, the named constant or derived type must have been declared previously in the scoping unit or made accessible by USE or host association.

R537

data_i_do_variable

is

scalar_int_variable

Constraint: data_i_do_variable must be a named variable.

Constraint: The DATA statement repeat factor must be positive or zero. If the DATA statement repeat factor is a named constant, it must have been declared previously in the scoping unit or made accessible by use association or host association.

Constraint: In a scalar_int_constant_subobject that is a data_stmt_repeat, any subscript must be an initialization expression.

Constraint: In a scalar_constant_subobject that is a data_stmt_constant, any subscript, substring starting point, or substring ending point must be an initialization expression.

Constraint: If a data_stmt_constant is a structure_constructor, each component must be an initialization expression.

Constraint: In a variable that is a data_stmt_object, any subscript, section subscript, substring starting point, and substring ending point must be an initialization expression.

Constraint: A variable whose name or designator is included in a data_stmt_object_list or a data_i_do_object_list must not be: a dummy argument; made accessible by use association or host association; in a named common block unless the DATA statement is in a block data program unit; in a blank common block, a function name, a function result name, an automatic object, or an allocatable array.

Constraint: In an array_element or a scalar_structure_component that is a data_i_do_object, any subscript must be an expression whose primaries are either constants, subobjects of constants, or DO variables of the containing data_implied_do elements, and each operation must be intrinsic.

Constraint: A scalar_int_expr of a data_implied_do must involve as primaries only constants, subobjects of constants, or DO variables of the containing data_implied_dos, and each operation must be intrinsic.

Constraint: The scalar_structure_component must contain at least one part_ref that contains a subscript_list.

EXT

typeless_constant

is

octal_typeless_constant

  

or

hexadecimal_typeless_constant

  

or

binary_typeless_constant

EXT

octal_typeless_constant

is

digit[digit] ... B

  

or

O" digit[digit] ... "

  

or

O' digit[digit] ... '

  

or

" digit[digit] ... "O

  

or

' digit[digit] ... 'O

EXT

hexadecimal_typeless_constant

is

X' hex_digit[hex_digit] ... '

  

or

X" hex_digit[hex_digit] ... "

  

or

' hex_digit[hex_digit] ... 'X

  

or

" hex_digit[hex_digit] ... "X

  

or

Z' hex_digit[hex_digit] ... '

  

or

Z" hex_digit[hex_digit] ... "

EXT

binary_typeless_constant

is

B' bin_digit[bin_digit] ... '

  

or

B" bin_digit[bin_digit] ... "

The following notes pertain to the definitions for typeless_constant, octal_typeless_constant, hexadecimal_typeless_constant, and binary_typeless_constant:

  • digit must have one of the values 0 through 7 in octal_typeless_constant

  • digit must have a value of 0 or 1 in binary_typeless_constant

  • The B, O, X, and Z characters can be in uppercase or lowercase.

R530

parameter_stmt

is

PARAMETER ( named_constant_def_list )

R531

named_constant_def

is

named_constant = initialization_expr

R541

implicit_stmt

is

IMPLICIT implicit_spec_list

  

or

IMPLICIT NONE

EXT

 

or

IMPLICIT UNDEFINED

R542

implicit_spec

is

type_spec ( letter_spec_list )

R543

letter_spec

is

letter[ - letter]

Constraint: If IMPLICIT NONE is specified in a scoping unit, it must precede any PARAMETER statements that appear in the scoping unit and there must be no other IMPLICIT statements in the scoping unit.

Constraint: If the minus and second letter appear, the second letter must follow the first letter alphabetically.

R544

namelist_stmt

is

NAMELIST / namelist_group_name / namelist_group_object_list[[ , ]
  / namelist_group_name / namelist_group_object_list] ...

R545

namelist_group_object

is

variable_name

Constraint: A namelist_group_object must not be an array dummy argument with a nonconstant bound, a variable with nonconstant character length, an automatic object, a pointer, a variable of a type that has an ultimate component that is a pointer, or an allocatable array.

Constraint: If a namelist_group_name has the PUBLIC attribute, no item in the namelist_group_object_list can have the PRIVATE attribute or have private components.

Constraint: The namelist_group_name must not be a name made accessible by USE association.

R546

equivalence_stmt

is

EQUIVALENCE equivalence_set_list

R547

equivalence_set

is

(equivalence_object, equivalence_object_list)

R548

equivalence_object

is

variable_name

  

or

array_element

  

or

substring

Constraint: An equivalence_object must not be a dummy argument, a pointer, an allocatable array, an object of a nonsequence derived type or of a sequence derived type containing a pointer at any level of component selection, an automatic object, a function name, an entry name, a result name, a named constant, a structure component, or a subobject of any of the preceding objects.

Constraint: An equivalence_object must not have the TARGET attribute.

Constraint: Each subscript or substring range expression in an equivalence_object must be an integer initialization expression.

Constraint: If an equivalence_object is of type default integer, default real, double-precision real, default complex, default logical, or numeric sequence type, all of the objects in the equivalence set must be of these types.

Constraint: If an equivalence_object is of type default character or character sequence type, all of the objects in the equivalence set must be of these types.

Constraint: If an equivalence_object is of a derived type that is not a numeric sequence or character sequence type, all of the objects in the equivalence set must be of the same type.

Constraint: If an equivalence_object is of an intrinsic type other than default integer, default real, double-precision real, default complex, default logical, or default character, all of the objects in the equivalence set must be of the same type with the same kind type parameter value.

Constraint: The name of an equivalence_object must not be a name made accessible by USE association.

Constraint: A substring must not have length zero.

R549

common_stmt

is

COMMON [ / [common_block_name] / ]common_block_object_list
[[ , ] / [common_block_name] / common_block_object_list] ...

R550

common_block_object

is

variable_name[ (explicit_shape_spec_list) ]

Constraint: Only one appearance of a given variable_name is permitted in all common_block_object_lists within a scoping unit.

Constraint: A common_block_object must not be a dummy argument, an allocatable array, an automatic object, a function name, an entry name, or a result name.

Constraint: Each bound in the explicit_shape_spec must be a constant specification expression.

Constraint: If a common_block_object is of a derived type, it must be a sequence type with no default initialization.

Constraint: If a variable_name appears with an explicit_shape_spec_list, it must not have the POINTER attribute.

Constraint: A variable name must not be a name made accessible by USE association.

Use of Data Objects

The following syntax rules are described in section 6, "Use of data objects," of the Fortran 95 standard.

R601

variable

is

scalar_variable_name

  

or

array_variable_name

  

or

subobject

Constraint: array_variable_name must be the name of a data object that is an array.

Constraint: array_variable_name must not have the PARAMETER attribute.

Constraint: scalar_variable_name must not have the PARAMETER attribute.

Constraint: subobject must not be a subobject designator (for example, a substring) whose parent is a constant.

R602

subobject

is

array_element

  

or

array_section

  

or

structure_component

  

or

substring

R603

logical_variable

is

variable

Constraint: logical_variable must be of type logical.

R604

default_logical_variable

is

variable

Constraint: default_logical_variable must be of type default logical.

R605

char_variable

is

variable

Constraint: char_variable must be of type character.

R606

default_char_variable

is

variable

Constraint: default_char_variable must be of type default character.

R607

int_variable

is

variable

Constraint: int_variable must be of type integer.

R608

default_int_variable

is

variable

Constraint: default_int_variable must be of type default integer.

R609

substring

is

parent_string ( substring_range )

R610

parent_string

is

scalar_variable_name

  

or

array_element

  

or

scalar_structure_component

  

or

scalar_constant

R611

substring_range

is

[scalar_int_expr] : [scalar_int_expr]

Constraint: parent_string must be of type character.

R612

data_ref

is

part_ref[ % part_ref] ...

R613

part_ref

is

part_name[ (section_subscript_list) ]

Constraint: In a data_ref, each part_name except the rightmost must be of derived type.

Constraint: In a data_ref, each part_name except the leftmost must be the name of a component of the derived type definition of the type of the preceding part_name.

Constraint: In a part_ref containing a section_subscript_list, the number of section_subscripts must equal the rank of part_name.

Constraint: In a data_ref, there must not be more than one part_ref with nonzero rank. A part_name to the right of a part_ref with nonzero rank must not have the POINTER attribute.

R614

structure_component

is

data_ref

Constraint: In a structure_component, there must be more than one part_ref and the rightmost part_ref must be of the form part_name.

R615

array_element

is

data_ref

Constraint: In an array_element, every part_ref must have rank zero and the last part_ref must contain a subscript_list.

R616

array_section

is

data_ref[ (substring_range) ]

Constraint: In an array_section, exactly one part_ref must have nonzero rank, and either the final part_ref has a section_subscript_list with nonzero rank or another part_ref must have nonzero rank.

Constraint: In an array_section with a substring_range, the rightmost part_name must be of type character.

R617

subscript

is

scalar_int_exp

R618

section_subscript

is

subscript

  

or

subscript_triplet

  

or

vector_subscript

R619

subscript_triplet

is

[subscript] : [subscript][ : stride]

R620

stride

is

scalar_int_expr

R621

vector_subscript

is

int_expr

Constraint: A vector_subscript must be an integer array expression of rank one.

Constraint: The second subscript must not be omitted from a subscript_triplet in the last dimension of an assumed-size array.

R622

allocate_stmt

is

ALLOCATE (allocation_list[, STAT = stat_variable] )

R623

stat_variable

is

scalar_int_variable

R624

allocation

is

allocate_object[ (allocate_shape_spec_list) ]

R625

allocate_object

is

variable_name

  

or

structure_component

R626

allocate_shape_spec

is

[allocate_lower_bound : ]allocate_upper_bound

R627

allocate_lower_bound

is

scalar_int_expr

R628

allocate_upper_bound

is

scalar_int_expr

Constraint: Each allocate_object must be a pointer or an allocatable array.

Constraint: The number of allocate_shape_specs in an allocate_shape_spec_list must be the same as the rank of the pointer or allocatable array.

R629

nullify_stmt

is

NULLIFY ( pointer_object_list )

R630

pointer_object

is

variable_name

  

or

structure_component

Constraint: Each pointer_object must have the POINTER attribute.

R631

deallocate_stmt

is

DEALLOCATE ( allocate_object_list[, STAT = stat_variable] )

Constraint: Each allocate_object must be a pointer or an allocatable array.

Expressions and Assignment

The following syntax rules are described in section 7, "Expressions and assignment," of the Fortran 95 standard.


Note:: The language of the Fortran 95 standard is presented in this subsection in its original form. Chapter 7 of the Fortran Language Reference Manual, Volume 1, however, sometimes uses terms that are different from those found in the standard. The terminology was changed to improve clarity. The following list shows the terms used in this compiler manual set and the equivalent term used in the Fortran 95 standard.


Standard

Silicon Graphics term

level_1_expr

defined_unary_expr

defined_unary_op

defined_operator

mult_operand

exponentiation_expr

power_op

**

add_operand

multiplication_expr

mult_op

* or /

level_2_expr

summation_expr

add_op

+ or -

level_3_expr

concatenation_expr

concat_op

//

level_4_expr

comparison_expr

rel_op

rel_op

and_operand

not_expr

not_op

.NOT.

or_operand

conjunct_expr

and_op

.AND.

or_op

.OR.

equiv_operand

inclusive_disjunct_expr

level_5_expr

equivalence_expr

mask_expr

logical_expr

R701

primary

is

constant

  

or

constant_subobject

  

or

variable

  

or

array_constructor

  

or

structure_constructor

  

or

function_reference

  

or

( expr )

R702

constant_subobject

is

subobject

Constraint: subobject must be a subobject designator whose parent is a constant. A variable that is a primary must not be an assumed-size array.

R703

level_1_expr

is

[defined_unary_op]primary

R704

defined_unary_op

is

.letter[letter] ... .

Constraint: A defined_unary_op must not contain more than 31 letters and must not be the same as any intrinsic_operator or logical_literal_constant.

R705

mult_operand

is

level_1_expr[power_opmult_operand]

R706

add_operand

is

[add_operand mult_op]mult_operand

R707

level_2_expr

is

[[level_2_expr]add_op]add_operand

R708

power_op

is

**

R709

mult_op

is

*

  

or

/

R710

add_op

is

+

  

or

-

R711

level_3_expr

is

[level_3_expr concat_op]level_2_expr

R712

concat_op

is

//

R713

level_4_expr

is

[level_3_expr rel_op]level_3_expr

R714

rel_op

is

.EQ.

 

 

or

.NE.

 

 

or

.LT.

 

 

or

.LE.

 

 

or

.GT.

 

 

or

.GE.

EXT

 

or

.LG.

 

 

or

==

 

 

or

/=

 

 

or

<

 

 

or

<=

 

 

or

>

 

 

or

>=

EXT

 

or

<>

R715

and_operand

is

[not_op]level_4_expr

R716

or_operand

is

[or_operandand_op]and_operand

R717

equiv_operand

is

[equiv_operand or_op]or_operand

R718

level_5_expr

is

[level_5_expr equiv_op]equiv_operand

R719

not_op

is

.NOT.

R720

and_op

is

.AND.

R721

or_op

is

.OR.

R722

equiv_op

is

.EQV.

  

or

.NEQV.

R723

expr

is

[expr defined_binary_op]level_5_expr

R724

defined_binary_op

is

.letter[letter] ... .

Constraint: A defined_binary_op must not contain more than 31 letters and must not be the same as any intrinsic_operator or logical_literal_constant.

R725

logical_expr

is

expr

Constraint: logical_expr must be type logical.

R726

char_expr

is

expr

Constraint: char_expr must be type character.

R727

default_char_expr

is

expr

Constraint: default_char_expr must be of type default character.

R728

int_expr

is

expr

Constraint: int_expr must be type integer.

R729

numeric_expr

is

expr

Constraint: numeric_expr must be of type integer, real, or complex.

R730

initialization_expr

is

expr

Constraint: An initialization_expr must be an initialization expression.

R731

char_initialization_expr

is

char_expr

Constraint: A char_initialization_expr must be an initialization expression.

R732

int_initialization_expr

is

int_expr

Constraint: An int_initialization_expr must be an initialization expression.

R733

logical_initialization_expr

is

logical_expr

Constraint: A logical_initialization_expr must be an initialization expression.

R734

specification_expr

is

scalar_int_expr

Constraint: The scalar_int_expr must be a restricted expression.

R735

assignment_stmt

is

variable = expr

Constraint: A variable in an assignment_stmt must not be an assumed-size array.

R736

pointer_assignment_stmt

is

pointer_object => target

R737

target

is

variable

  

or

expr

Constraint: The pointer_object must have the POINTER attribute.

Constraint: The variable must have the TARGET attribute or be a subobject of an object with the TARGET attribute, or it must have the POINTER attribute.

Constraint: The target must be of the same type, kind type parameters, and rank as the pointer.

Constraint: The target must not be an array section with a vector subscript.

Constraint: The expr must deliver a pointer result.

R738

where_stmt

is

WHERE ( mask_expr ) where_assignment_stmt

R739

where_construct

is

where_construct_stmt
[where_body_construct] ...
[masked_elsewhere_stmt
[where_body_construct] ...] ...
[elsewhere_stmt
[where_body_construct] ...

]end_where_stmt

R740

where_construct_stmt

is

[where_construct_name:]WHERE ( mask_expr )

R741

where_construct_stmt

is

where_assignment_stmt

  

or

where_stmt

  

or

where_construct

R742

where_assignment_stmt

is

assignment_stmt

R743

mask_expr

is

logical_expr

R742

masked_elsewhere_stmt

is

ELSEWHERE (mask_expr) [where_construct_name]

R745

elsewhere_stmt

is

ELSEWHERE [where_construct_name]

R746

end_where_stmt

is

END WHERE [where_construct_name]

Constraint: A where_assignment_stmt that is a defined assignment must be elemental.

Constraint: If the where_construct_stmt is identified by a where_construct_name, the corresponding end_where_stmt must specify the same where_construct_name. If the where_construct_stmt is not identified by a where_construct_name, the corresponding end_where_stmt must not specify a where_construct_name. If an elsewhere_stmt or a masked_elsewhere_stmt is identified by a where_construct_name, the corresponding where_construct_stmt must specify the same where_construct_name.

R747

forall_construct

is

forall_construct_stmt
[forall_body_construct] ...
end_forall_stmt

R748

forall_construct_stmt

is

[forall_construct_name:]FORALL forall_header

R749

forall_header

is

(forall_triplet_spec_list[, scalar_mask_expr])

R750

forall_triplet_spec

is

index_name = subscript : subscript[: stride]

R617

subscript

is

scalar_int_expr

R603

stride

is

scalar_int_expr

R751

forall_body_construct

is

forall_assignment_stmt

R751

forall_body_construct

is

forall_assignment_stmt

  

or

where_stmt

  

or

where_construct

  

or

forall_construct

  

or

forall_stmt

R752

forall_assignment_stmt

is

assignment_stmt

  

or

pointer_assignment_stmt

R753

end_forall_stmt

is

END FORALL [forall_construct_name]

Constraint: If the forall_construct_stmt has a forall_construct_name, the end_forall_stmt must have the same forall_construct_name. If the end_forall_stmt has a forall_construct_name, the forall_construct_stmt must have the same forall_construct_name.

Constraint: The scalar_mask_expr must be scalar and of type logical.

Constraint: Any procedure referenced in the scalar_mask_expr, including one referenced by a defined operation, must be a pure procedure.

Constraint: The index_name must be a named scalar variable of type integer.

Constraint: A subscript or stride in a forall_triplet_spec must not contain a reference to any index_name in the forall_triplet_spec_list in which it appears.

Constraint: A statement in a forall_body_construct must not define an index_name of the forall_construct.

Constraint: Any procedure referenced in a forall_body_construct, including one referenced by a defined operation or assignment, must be a pure procedure.

Constraint: A forall_body_construct must not be a branch target.

R754

forall_stmt

is

FORALL forall_headerforall_assignment_stmt


Execution Control

The following syntax rules are described in section 8, "Execution control," of the Fortran 95 standard.

R801

block

is

[execution_part_construct] ...

R802

if_construct

is

if_then_stmt
block
[else_if_stmt
block] ...
[else_stmt
block]
end_if_stmt

R803

if_then_stmt

is

[if_construct_name : ] IF ( scalar_logical_expr ) THEN

R804

else_if_stmt

is

ELSE IF ( scalar_logical_expr )
  THEN [if_construct_name]

R805

else_stmt

is

ELSE [if_construct_name]

R806

end_if_stmt

is

END IF [if_construct_name]

Constraint: If the if_then_stmt of an if_construct is identified by an if_construct_name, the corresponding end_if_stmt must specify the same if_construct_name. If the if_then_stmt of an if_construct is not identified by an if_construct_name, the corresponding end_if_stmt must not specify an if_construct_name. If an else_if_stmt or else_stmt is identified by an if_construct_name, the corresponding if_then_stmt must specify the same if_construct_name.

R807

if_stmt

is

IF (scalar_logical_expr) action_stmt

Constraint: The action_stmt in the if_stmt must not be an if_stmt, end_program_stmt, end_function_stmt, or end_subroutine_stmt.

R808

case_construct

is

select_case_stmt
[case_stmt
block] ...
end_select_stmt

R809

select_case_stmt

is

[case_construct_name] : SELECT CASE ( case_expr )

R810

case_stmt

is

CASE case_selector[case_construct_name]

R811

end_select_stmt

is

END SELECT [case_construct_name]

Constraint: If the select_case_stmt of a case_construct is identified by a case_construct_name, the corresponding end_select_stmt must specify the same case_construct_name. If the select_case_stmt of a case_construct is not identified by a case_construct_name, the corresponding end_select_stmt must not specify a case_construct_name. If a case_stmt is identified by a case_construct_name, the corresponding select_case_stmt must specify the same case_construct_name.

R812

case_expr

is

scalar_int_expr

  

or

scalar_char_expr

  

or

scalar_logical_expr

R813

case_selector

is

( case_value_range_list )

  

or

DEFAULT

Constraint: No more than one of the selectors of one of the CASE statements may be DEFAULT.

R814

case_value_range

is

case_value

  

or

case_value :

  

or

: case_value

  

or

case_value : case_value

R815

case_value

is

scalar_int_initialization_expr

  

or

scalar_char_initialization_expr

  

or

scalar_logical_initialization_expr

Constraint: For a given case_construct, each case_value must be of the same type as case_expr. For character type, length differences are allowed, but the kind type parameters must be the same.

Constraint: A case_value_range using a colon must not be used if case_expr is of type logical.

Constraint: For a given case_construct, the case_value_ranges must not overlap; that is, there must be no possible value of the case_expr that matches more than one case_value_range.

R816

do_construct

is

block_do_construct

  

or

nonblock_do_construct

R817

block_do_construct

is

do_stmt
do_block
end_do

R818

do_stmt

is

label_do_stmt

  

or

nonlabel_do_stmt

R819

label_do_stmt

is

[do_construct_name : ] DO label[loop_control]

R820

nonlabel_do_stmt

is

[do_construct_name : ] DO [loop_control]

R821

loop_control

is

[ , ]do_variable = scalar_int_expr,

  

or

scalar_int_expr[, scalar_int_expr]

   

[ , ] WHILE ( scalar_logical_expr )

R822

do_variable

is

scalar_int_variable

Constraint: The do_variable must be a named scalar variable of type integer, default real, or double-precision real. The Fortran standard does not allow for do_variables of type default real or double-precision real.

Constraint: Each scalar_numeric_expr in loop_control must be of type integer, default real, or double-precision real. The Fortran standard does not allow for do_variables of type default real or double-precision real.

R823

do_block

is

block

R824

end_do

is

end_do_stmt

  

or

continue_stmt

R825

end_do_stmt

is

END DO [do_construct_name]

Constraint: If the do_stmt of a block_do_construct is identified by a do_construct_name, the corresponding end_do must be an end_do_stmt specifying the same do_construct_name. If the do_stmt of a block_do_construct is not identified by a do_construct_name, the corresponding end_do must not specify a do_construct_name.

Constraint: If the do_stmt is a nonlabel_do_stmt, the corresponding end_do must be an end_do_stmt.

Constraint: If the do_stmt is a label_do_stmt, the corresponding end_do must be identified with the same label.

OBS

nonblock_do_construct

is

action_term_do_construct

  

or

outer_shared_do_construct

OBS

action_term_do_construct

is

label_do_stmt
do_body
do_term_action_stmt

OBS

do_body

is

[execution_part_construct] ...

OBS

do_term_action_stmt

is

action_stmt

Obsolescent Constraint: A do_term_action_stmt must not be a continue_stmt, a goto_stmt, a return_stmt, a stop_stmt, an exit_stmt, a cycle_stmt, an end_function_stmt, an end_subroutine_stmt, an end_program_stmt, or an arithmetic_if_stmt.

Obsolescent Constraint: The do_term_action_stmt must be identified with a label and the corresponding label_do_stmt must refer to the same label.

OBS

outer_shared_do_construct

is

label_do_stmt
do_body
shared_term_do_construct

OBS

shared_term_do_construct

is

outer_shared_do_construct

  

or

inner_shared_do_construct

OBS

inner_shared_do_construct

is

label_do_stmt
do_body
do_term_shared_stmt

OBS

do_term_shared_stmt

is

action_stmt

Obsolescent Constraint: A do_term_shared_stmt must not be a goto_stmt, a return_stmt, a stop_stmt, an exit_stmt, a cycle_stmt, an end_function_stmt, an end_subroutine_stmt, an end_program_stmt, or an arithmetic_if_stmt.

Obsolescent Constraint: The do_term_shared_stmt must be identified with a label, and all of the label_do_stmts of the shared_term_do_construct must refer to the same label.

R834

cycle_stmt

is

CYCLE [do_construct_name]

Constraint: If a cycle_stmt refers to a do_construct_name, it must be within the range of that do_construct; otherwise, it must be within the range of at least one do_construct.

R835

exit_stmt

is

EXIT [do_construct_name]

Constraint: If an exit_stmt refers to a do_construct_name, it must be within the range of that do_construct; otherwise, it must be within the range of at least one do_construct.

R836

goto_stmt

is

GO TO label

Constraint: The label must be the statement label of a branch target statement that appears in the same scoping unit as the goto_stmt.

OBS

computed_goto_stmt

is

GO TO ( label_list ) [ , ]scalar_int_expr

Obsolescent Constraint: Each label in label_list must be the statement label of a branch target statement that appears in the same scoping unit as the computed_goto_stmt.

EXT

assign_stmt

is

ASSIGN label TO scalar_int_variable

Extension Constraint: The label must be the statement label of a branch target statement or format_stmt that appears in the same scoping unit as the assign_stmt.

Extension Constraint: scalar_int_variable must be named and of type default integer.

EXT

assigned_goto_stmt

is

GO TO scalar_int_variable[[ , ] (label_list) ]

Extension Constraint: Each label in label_list must be the statement label of a branch target statement that appears in the same scoping unit as the assigned_goto_stmt.

Extension Constraint: scalar_int_variable must be named and of type default integer.

OBS

arithmetic_if_stmt

is

IF ( scalar_numeric_expr ) label, label, label

Obsolescent Constraint: Each label must be the label of a branch target statement that appears in the same scoping unit as the arithmetic_if_stmt.

Obsolescent Constraint: The scalar_numeric_expr must not be of type complex.

R839

continue_stmt

is

CONTINUE

R840

stop_stmt

is

STOP [stop_code]

R841

stop_code

is

scalar_char_constant

EXT

 

or

digit[digit[digit[digit[digit]]]]

Constraint: scalar_char_constant must be of type default character.

EXT

pause_stmt

is

PAUSE [stop_code]


Input/Output (I/O) Statements

The following syntax rules are described in section 9, "Input/Output statements," of the Fortran 95 standard.

R901

io_unit

is

external_file_unit

 

 

or

*

 

 

or

internal_file_unit

EXT

 

or

unit_name

R902

external_file_unit

is

scalar_int_expr

R903

internal_file_unit

is

default_char_variable

Constraint: The default_char_variable must not be an array section with a vector subscript.

R904

open_stmt

is

OPEN ( connect_spec_list )

R905

connect_spec

is

[ UNIT = ]external_file_unit

  

or

IOSTAT = scalar_default_int_variable

  

or

ERR = label

  

or

FILE = file_name_expr

  

or

STATUS = scalar_char_expr

  

or

ACCESS = scalar_char_expr

  

or

FORM = scalar_char_expr

  

or

RECL = scalar_int_expr

  

or

BLANK = scalar_char_expr

  

or

POSITION = scalar_char_expr

  

or

ACTION = scalar_char_expr

  

or

DELIM = scalar_char_expr

  

or

PAD = scalar_char_expr

R906

file_name_expr

is

scalar_char_expr

Constraint: If the optional characters UNIT= are omitted from the unit specifier, the unit specifier must be the first item in the connect_spec_list.

Constraint: Each specifier must not appear more than once in a given open_stmt; an external_file_unit must be specified.

Constraint: The label used in the ERR= specifier must be the statement label of a branch target statement that appears in the same scoping unit as the OPEN statement.

R907

close_stmt

is

CLOSE ( close_spec_list )

R908

close_spec

is

[ UNIT = ]external_file_unit

  

or

IOSTAT = scalar_default_int_variable

  

or

ERR = label

  

or

STATUS = scalar_char_expr

Constraint: If the optional characters UNIT= are omitted from the unit specifier, the unit specifier must be the first item in the close_spec_list.

Constraint: Each specifier must not appear more than once in a given close_stmt; an external_file_unit must be specified.

Constraint: The label used in the ERR= specifier must be the statement label of a branch target statement that appears in the same scoping unit as the CLOSE statement.

R909

read_stmt

is

READ ( io_control_spec_list ) [input_item_list]

EXT

 

or

READ format[ , input_item_list]

R910

write_stmt

is

WRITE ( io_control_spec_list ) [output_item_list]

EXT

 

or

WRITE format[ , output_item_list]

R911

print_stmt

is

PRINT format[ , output_item_list]

R912

io_control_spec

is

[ UNIT = ]io_unit

  

or

[ FMT = ]format

  

or

[ NML = ]namelist_group_name

  

or

REC = scalar_int_expr

  

or

IOSTAT = scalar_default_int_variable

  

or

ERR = label

  

or

END = label

  

or

ADVANCE = scalar_default_char_expr

  

or

SIZE = scalar_default_int_variable

  

or

EOR = label

Constraint: An io_control_spec_list must contain exactly one io_unit and may contain at most one of each of the other specifiers.

Constraint: An END=, EOR=, or SIZE= specifier must not appear in a write_stmt.

Constraint: The label in the ERR=, EOR=, or END= specifier must be the statement label of a branch target statement that appears in the same scoping unit as the data transfer statement.

Constraint: A namelist_group_name must not be present if an input_item_list or an output_item_list is present in the data transfer statement.

Constraint: An io_control_spec_list must not contain both a format and a namelist_group_name.

Constraint: If the optional characters UNIT= are omitted from the unit specifier, the unit specifier must be the first item in the control information list.

Constraint: If the optional characters FMT= are omitted from the format specifier, the format specifier must be the second item in the control information list and the first item must be the unit specifier without the optional characters UNIT=.

Constraint: If the optional characters NML= are omitted from the namelist specifier, the namelist specifier must be the second item in the control information list and the first item must be the unit specifier without the optional characters UNIT=.

Constraint: If the unit specifier specifies an internal file, the io_control_spec_list must not contain a REC= specifier or a namelist_group_name.

Constraint: If the REC= specifier is present, an END= specifier must not appear, a namelist_group_name must not appear, and the format, if any, must not be an asterisk specifying list_directed I/O.

Constraint: An ADVANCE= specifier may be present only in a formatted sequential I/O statement with explicit format specification whose control information list does not contain an internal file unit specifier.

Constraint: If an EOR= specifier is present, an ADVANCE= specifier also must appear.

Constraint: If a SIZE= specifier is present, an ADVANCE= specifier must also appear.

R913

format

is

default_char_expr

  

or

label

  

or

*

EXT

 

or

scalar_default_int_variable

Constraint: The label must be the label of a FORMAT statement that appears in the same scoping unit as the statement containing the format specifier.

R914

input_item

is

variable

  

or

io_implied_do

R915

output_item

is

expr

  

or

io_implied_do

R916

io_implied_do

is

( io_implied_do_object_list, io_implied_do_control )

R917

io_implied_do_object

is

input_item

  

or

output_item

R918

io_implied_do_control

is

do_variable = scalar_int_expr,
scalar_int_expr[, scalar_int_expr]

Constraint: A variable that is an input_item must not be an assumed-size array.

Constraint: The DO variable must be a named scalar of type integer.

Constraint: In an input_item_list, an io_implied_do_object must be an input_item. In an output_item_list, an io_implied_do_object must be an output_item.

EXT

buffer_in_stmt

is

BUFFER IN (io_unit, mode) (start_loc, end_loc)

EXT

buffer_out_stmt

is

BUFFER OUT (io_unit, mode) (start_loc, end_loc)

EXT

io_unit

is

external_file_unit

  

or

file_name_expr

EXT

mode

is

scalar_integer_expr

EXT

start_loc

is

variable

EXT

end_loc

is

variable

In the preceding definition, the variable specified for start_loc and end_loc cannot be of a derived type if you are performing implicit data conversion. The data items between start_loc and end_loc must be of the same type and same kind type.

R919

backspace_stmt

is

BACKSPACE external_file_unit

  

or

BACKSPACE ( position_spec_list )

R920

endfile_stmt

is

ENDFILE external_file_unit

  

or

ENDFILE ( position_spec_list )

R921

rewind_stmt

is

REWIND external_file_unit

  

or

REWIND ( position_spec_list )

R922

position_spec

is

[ UNIT = ]external_file_unit

  

or

IOSTAT = scalar_default_int_variable

  

or

ERR = label

Constraint: The label in the ERR= specifier must be the statement label of a branch target statement that appears in the same scoping unit as the file positioning statement.

Constraint: If the optional characters UNIT= are omitted from the unit specifier; the unit specifier must be the first item in the position_spec_list.

Constraint: A position_spec_list must contain exactly one external_file_unit and may contain at most one of each of the other specifiers.

R923

inquire_stmt

is

INQUIRE ( inquire_spec_list )

  

or

INQUIRE ( IOLENGTH = scalar_default_int_variable ) output_item_list

R924

inquire_spec

is

[ UNIT = ]external_file_unit

  

or

FILE = file_name_expr

  

or

IOSTAT = scalar_default_int_variable

  

or

ERR = label

  

or

EXIST = scalar_default_logical_variable

  

or

OPENED = scalar_default_logical_variable

  

or

NUMBER = scalar_default_int_variable

  

or

NAMED = scalar_default_logical_variable

  

or

NAME = scalar_default_ char_variable

  

or

ACCESS = scalar_default_char_variable

  

or

SEQUENTIAL = scalar_default_char_variable

  

or

DIRECT = scalar_default_char_variable

  

or

FORM = scalar_default_char_variable

  

or

FORMATTED = scalar_default_char_variable

  

or

UNFORMATTED = scalar_default_char_variable

  

or

RECL = scalar_default_int_variable

  

or

NEXTREC = scalar_default_int_variable

  

or

BLANK = scalar_default_char_variable

  

or

POSITION = scalar_default_char_variable

  

or

ACTION = scalar_default_char_variable

  

or

READ = scalar_default_char_variable

  

or

WRITE = scalar_default_char_variable

  

or

READWRITE = scalar_default_char_variable

  

or

DELIM = scalar_default_char_variable

  

or

PAD = scalar_default_char_variable

Constraint: An inquire_spec_list must contain one FILE= specifier or one UNIT= specifier, but not both, and at most one of each of the other specifiers.

Constraint: In the inquire by unit form of the INQUIRE statement, if the optional characters UNIT= are omitted from the unit specifier, the unit specifier must be the first item in the inquire_spec_list.

I/O Editing

The following syntax rules are described in section 10, "Input/Output editing," of the Fortran 95 standard.

R1001

format_stmt

is

FORMAT format_specification

R1002

format_specification

is

( [format_item_list] )

Constraint: The format_stmt must be labeled.

Constraint: The comma used to separate format_items in a format_item_list may be omitted as follows:

  • Between a P edit descriptor and an immediately following F, E, EN, ES, D, or G edit descriptor

  • Before a slash edit descriptor when the optional repeat specification is not present

  • After a slash edit descriptor

  • Before or after a colon edit descriptor

R1003

format_item

is

[r]data_edit_desc

  

or

control_edit_desc

  

or

char_string_edit_desc

  

or

[r] ( format_item_list )

R1004

r

is

int_literal_constant

Constraint: r must be positive.

Constraint: r must not have kind parameter specified for it.

R1005

data_edit_desc

is

I w[ . m]

 

 

or

B w[ . m]

 

 

or

O w[ . m]

 

 

or

Z w[ . m]

 

 

or

F w . d

 

 

or

E w . d[ E e]

 

 

or

EN w . d[ E e]

 

 

or

ES w . d[ E e]

 

 

or

G w . d[ E e]

 

 

or

L w

 

 

or

A [w]

 

 

or

D w . d

EXT

 

or

D w . d E e

EXT

 

or

R w

EXT

 

or

Q

R1006

w

is

int_literal_constant

R1007

m

is

int_literal_constant

R1008

d

is

int_literal_constant

R1009

e

is

int_literal_constant

Constraint: e must be positive.

Constraint: w must be zero or positive for the I, B, O, Z, and F edit descriptors. w must be positive for all other edit descriptors.

Constraint: w, m, d, and e must not have kind parameters specified for them.

R1010

control_edit_desc

is

position_edit_desc

  

or

[r] /

  

or

:

  

or

sign_edit_desc

  

or

k P

  

or

blank_interp_edit_desc

R1011

k

is

signed_int_literal_constant

Constraint: k must not have a kind parameter specified for it.

R1012

position_edit_desc

is

T n

 

 

or

TL n

 

 

or

TR n

 

 

or

n X

EXT

 

or

\

EXT

 

or

$

R1013

n

is

int_literal_constant

Constraint: n must be positive.

Constraint: n must not have a kind parameter specified for it.

R1014

sign_edit_desc

is

S

  

or

SP

  

or

SS

R1015

blank_interp_edit_desc

is

BN

  

or

BZ

R1016

char_string_edit_desc

is

char_literal_constant

EXT

 

or

c H rep_char[rep_char] ...

EXT

c

is

int_literal_constant

Constraint: The char_literal_constant must not have a kind parameter specified for it.

Program Units

The following syntax rules are described in section 11, "Program units," of the Fortran 95 standard.

R1101

main_program

is

[program_stmt]
[specification_part]
[execution_part]
[internal_subprogram_part]
end_program_stmt

R1102

program_stmt

is

PROGRAM program_name[ (args) ]

EXT

args

is

Any character in the CF90 character

   

  set. The CF90 compiler ignores any

   

args specified after program_name.

R1103

end_program_stmt

is

END [ PROGRAM [program_name]]

Constraint: In a main_program, the execution_part must not contain a RETURN statement or an ENTRY statement.

Constraint: The program_name may be included in the end_program_stmt only if the optional program_stmt is used and, if included, must be identical to the program_name specified in the program_stmt.

Constraint: An automatic object must not appear in the specification_part of a main program.

R1104

module

is

module_stmt
[specification_part]
[module_subprogram_part]
end_module_stmt

R1105

module_stmt

is

MODULE module_name

R1106

end_module_stmt

is

END [ MODULE [module_name]]

Constraint: If the module_name is specified in the end_module_stmt, it must be identical to the module_name specified in the module_stmt.

Constraint: A module specification_part must not contain a stmt_function_stmt, an entry_stmt, or a format_stmt.

Constraint: An automatic object must not appear in the specification_part of a module.

Constraint: If an object of a type for which component_initialization is specified appears in the specification_part of a module and does not have the ALLOCATABLE or POINTER attribute, the object must have the SAVE attribute.

R1107

use_stmt

is

USE module_name[, rename_list]

  

or

USE module_name, ONLY : [only_list]

R1108

rename

is

local_name => use_name

R1109

only

is

generic_spec

  

or

only_use_name

  

or

only_rename

R1110

only_use_name

is

use_name

R1111

only_rename

is

local_name => use_name

Constraint: Each generic_spec must be a public entity in the module.

Constraint: Each use_name must be the name of a public entity in the module.

R1112

block_data

is

block_data_stmt
[specification_part]
end_block_data_stmt

R1113

block_data_stmt

is

BLOCK DATA [block_data_name]

R1114

end_block_data_stmt

is

END [ BLOCK DATA [block_data_name]]

Constraint: The block_data_name may be included in the end_block_data_stmt only if it was provided in the block_data_stmt and, if included, must be identical to the block_data_name in the block_data_stmt.

Constraint: A block_dataspecification_part may contain only USE statements, type declaration statements, IMPLICIT statements, PARAMETER statements, derived-type definitions, and the following specification statements: COMMON, DATA, DIMENSION, EQUIVALENCE, INTRINSIC, POINTER, SAVE, and TARGET.

Constraint: A type declaration statement in a block_dataspecification_part must not contain ALLOCATABLE, EXTERNAL, INTENT, OPTIONAL, PRIVATE, or PUBLIC attribute specifiers.

Procedures

The following syntax rules are described in section 12, "Procedures," of the Fortran 95 standard.

R1201

interface_block

is

interface_stmt
[interface_specification] ...
end_interface_stmt

R1202

interface_specification

is

interface_body

 

 

or

module_procedure_stmt

R1203

interface_stmt

is

INTERFACE [generic_spec]

R1204

end_interface_stmt

is

END INTERFACE [generic_spec]

R1204

interface_body

is

function_stmt

  

 

[specification_part]

  

 

end_function_stmt

  

or

subroutine_stmt

   

[specification_part]

   

end_subroutine_stmt

R1206

module_procedure_stmt

is

MODULE PROCEDURE procedure_name_list

R1207

generic_spec

is

generic_name

  

or

OPERATOR ( defined_operator )

  

or

ASSIGNMENT ( = )

Constraint: An interface body of a pure procedure must specify the intents of all dummy procedures except pointer, alternate return, and procedure arguments.

Constraint: An interface_body must not contain an entry_stmt, data_stmt, format_stmt, or stmt_function_stmt.

Constraint: The MODULE PROCEDURE statement is allowed only if the interface_block has a generic_spec and is in a scoping unit where each procedure_name is accessible as a module procedure.

Constraint: An interface_block in a subprogram must not contain an interface_body for a procedure defined by that subprogram.

Constraint: A procedure_name in a module_procedure_stmt must not be one that previously had been established to be associated with the generic_spec of the interface_block in which it appears, either by a previous appearance in an interface_block or by use or host association.

Constraint: The generic_spec can be included in the end_interface_stmt only if it was provided in the interface_stmt. If included, it must be identical to the generic_spec in the interface_stmt.

R1208

external_stmt

is

EXTERNAL [::]external_name_list

R1209

intrinsic_stmt

is

INTRINSIC [::]intrinsic_procedure_name_list

Constraint: Each intrinsic_procedure_name must be the name of an intrinsic procedure.

R1210

function_reference

is

function_name ([actual_arg_spec_list])

Constraint: The actual_arg_spec_list for a function reference must not contain an alt_return_spec.

R1211

call_stmt

is

CALL subroutine_name[([actual_arg_spec_list])]

R1212

actual_arg_spec

is

[keyword = ]actual_arg

R1213

keyword

is

dummy_arg_name

R1214

actual_arg

is

expr

  

or

variable

  

or

procedure_name

OBS

 

or

alt_return_spec

R1215

alt_return_spec

is

* label

Constraint: The keyword = must not appear if the interface of the procedure is implicit in the scoping unit.

Constraint: The keyword = may be omitted from an actual_arg_spec only if the keyword = has been omitted from each preceding actual_arg_spec in the argument list.

Constraint: Each keyword must be the name of a dummy argument in the explicit interface of the procedure.

Constraint: A procedure_nameactual_arg must not be the name of an internal procedure or of a statement function and must not be the generic name of a procedure.

Constraint: The label used in the alt_return_spec must be the statement label of a branch target statement that appears in the same scoping unit as the call_stmt.

Constraint: A nonintrinsic elemental procedure must not be used as an actual argument.

Constraint: In a reference to a pure procedure, a procedure_nameactual_arg must be the name of a pure procedure.

R1216

function_subprogram

is

function_stmt
[specification_part]
[execution_part]
[internal_subprogram_part]
end_function_stmt

R1217

function_stmt

is

[prefix] FUNCTION function_name
  ( [dummy_arg_name_list] )
[ RESULT ( result_name )]

Constraint: If RESULT is specified, the function_name must not appear in any specification statement in the scoping unit of the function subprogram.

Constraint: A prefix must contain at most one of each prefix_spec.

Constraint: If ELEMENTAL is present, RECURSIVE must not be present.

R1218

prefix

is

prefix_spec[prefix_spec] ...

R1219

prefix_spec

is

type_spec

  

or

RECURSIVE

  

or

PURE

  

or

ELEMENTAL

R1220

end_function_stmt

is

END [ FUNCTION [function_name]]

Constraint: If RESULT is specified, result_name must not be the same as function_name.

Constraint: FUNCTION must be present on the end_function_stmt of an internal or module function.

Constraint: An internal function subprogram must not contain an ENTRY statement.

Constraint: An internal function subprogram must not contain an internal_subprogram_part.

Constraint: If a function_name is present on the end_function_stmt, it must be identical to the function_name specified in the function_stmt.

R1221

subroutine_subprogram

is

subroutine_stmt
[specification_part]
[execution_part]
[internal_subprogram_part]
end_subroutine_stmt

R1222

subroutine_stmt

is

[prefix]SUBROUTINEsubroutine_name[( [dummy_arg_list] )]

R1223

dummy_arg

is

dummy_arg_name

  

or

*

R1224

end_subroutine_stmt

is

END [ SUBROUTINE [subroutine_name]]

Constraint: The prefix of a subroutine_stmt must not contain a type_spec.

Constraint: SUBROUTINE must be present on the end_subroutine_stmt of an internal or module subroutine.

Constraint: An internal subroutine must not contain an ENTRY statement.

Constraint: An internal subroutine must not contain an internal_subprogram_part.

Constraint: If a subroutine_name is present on the end_subroutine_stmt, it must be identical to the subroutine_name specified in the subroutine_stmt.

R1225

entry_stmt

is

ENTRY entry_name[( [dummy_arg_list] ) [RESULT ( result_name )]]

Constraint: If RESULT is specified, the entry_name must not appear in any specification statement in the scoping unit of the function program.

Constraint: An entry_stmt may appear only in an external_subprogram or module_subprogram. An entry_stmt must not appear within an executable_construct.

Constraint: RESULT may be present only if the entry_stmt is contained in a function subprogram.

Constraint: Within the subprogram containing the entry_stmt, the entry_name must not appear as a dummy argument in the FUNCTION or SUBROUTINE statement or in another ENTRY statement and it must not appear in an EXTERNAL or INTRINSIC statement.

Constraint: A dummy_arg can be an alternate return indicator only if the ENTRY statement is in a subroutine subprogram.

Constraint: If RESULT is specified, result_name must not be the same as entry_name.

R1226

return_stmt

is

RETURN

OBS

 

or

RETURN [scalar_int_expr]

Constraint: The return_stmt must be in the scoping unit of a function or subroutine subprogram.

Obsolescent Constraint: The scalar_int_expr is allowed only in the scoping unit of a subroutine subprogram.

R1227

contains_stmt

is

CONTAINS

R1228

stmt_function_stmt

is

function_name ([dummy_arg_name_list]) = scalar_expr

Obsolescent Constraint: The primaries of the scalar_expr must be constants (literal and named), references to variables, references to functions and function dummy procedures, and intrinsic operations. If scalar_expr contains a reference to a function or function dummy procedure, the reference must not require an explicit interface; the function must not require an explicit interface unless it is an intrinsic; the function must not be a transformational intrinsic; and the result must be scalar. If an argument to a function or a function dummy procedure is array valued, it must be an array name. If a reference to a statement function appears in scalar_expr, its definition must have been provided earlier in the scoping unit and must not be the name of the statement function being defined.

Obsolescent Constraint: Named constants in scalar_expr must have been declared earlier in the scoping unit or made accessible by USE or host association. If array elements appear in scalar_expr, the parent array must not have been declared as an array earlier in the scoping unit or made accessible by USE or host association.

Obsolescent Constraint: If a dummy_arg_name, variable, function reference, or dummy function reference is typed by the implicit typing rules, its appearance in any subsequent type declaration statement must confirm this implied type and the values of any implied type parameters.

Constraint: The function_name and each dummy_arg_name must be specified, explicitly or implicitly, to be scalar data objects.

Constraint: A given dummy_arg_name may appear only once in any dummy_arg_name_list.

Constraint: Each scalar variable reference in scalar_expr may be either a reference to a dummy argument of the statement function or a reference to a variable local to the same scoping unit as the statement function statement.

Constraint: The specification_part of a pure function subprogram must specify that all dummy arguments have INTENT(IN) except procedure arguments and arguments with the POINTER attribute.

Constraint: The specification_part of a pure subroutine subprogram must specify the intents of all dummy arguments except procedure arguments, alternate return indicators, and arguments with the POINTER attribute. Note that alternate return indicators are obsolete.

Constraint: A local variable declared in the specification_part or internal_subprogram_part of a pure subprogram must not have the SAVE attribute.

Constraint: The specification_part of a pure subprogram must specify that all dummy arguments that are procedure arguments are pure.

Constraint: If a procedure that is neither an intrinsic procedure nor a statement function is used in a context that requires it to be pure, its interface must be explicit in the scope of that use. The interface must specify that the procedure is pure. Note that statement functions are obsolete.

Constraint: All internal subprograms in a pure subprogram must be pure.

Constraint: In a pure subprogram, any variable that is in common or is accessed by host or USE association, is a dummy argument to a pure function, is a dummy argument with INTENT(IN) to a pure subroutine, or an object that is storage associated with any such variable, must not be used in the following contexts:

  • As the variable of an assignment_stmt

  • As a DO variable or implied DO variable

  • As an input_item in a read_stmt from an internal file

  • As an internal_file_unit in a write_stmt

  • As an IOSTAT= specifier in an input or output statement with an internal file

  • As the pointer_object of a pointer_assignment_stmt

  • As the target of a pointer_assignment_stmt

  • As the expr of an assignment_stmt in which the variable is of a derived type if the derived type has a pointer component at any level of component selection

  • As an allocate_object or stat_variable in an allocate_stmt or deallocate_stmt, or as a pointer_object in a nullify_stmt

  • As an actual argument associated with a dummy argument with INTENT(OUT) or INTENT(INOUT) or with the POINTER attribute

Constraint: Any procedure referenced in a pure subprogram, including one referenced via a defined operation or assignment, must be pure.

Constraint: A pure subprogram must not contain a print_stmt, open_stmt, close_stmt, backspace_stmt, endfile_stmt, rewind_stmt, or inquire_stmt.

Constraint: A pure subprogram must not contain a read_stmt or write_stmt with an io_unit that is an external_file_unit or an asterisk (*).

Constraint: A pure subprogram must not contain a stop_stmt.

Intrinsic Procedures

There are no syntax rules described in section 13, "Intrinsic procedures," of the Fortran 95 standard.

Scope, Association, and Definition

There are no syntax rules described in section 14, "Scope, association, and definition," of the Fortran 95 standard.