![]() ![]() ![]() ![]() ![]() |
![]() Essential Lahey Fortran 90 Syntax |
The following text (syntax rules for Essential Lahey Fortran 90,
Version 2.00) are derived from the electronic version of the Fortran 90
standard, Appendix D.
The following changes have been made to the Appendix D text: Lines have been reformatted so as to have at most 75 characters plus end of line. Where needed text was realigned. In rearranging the text, page numbers and printed line-numbers agree with the printed version of the standard, not the electronic version. Sometimes, the blank lines within consecutively numbered lines were collected at the end of the block. Blank lines were not numbered in Appendix D and are not here. In this document, when a blank line is numbered, it means that Appendix D text was deleted because Essential LF90 does not allow the syntax or that a constraint is not applicable. A line without a line number but with text indicates an Essential LF90 re- quirement that was optional in the standard, e.g., IMPLICIT NONE. Unneeded syntax rules (see 507 which could be folded into 506) were not eliminated in order to preserve a higher isomorphism to the text in the standard. The constraint at Page 312 appears in the electronic version, not the printed version. To reduce the length of long lines, the following substitutions were made within the syntax rules: literal was replaced with lit exponent was replaced with xpn initialization was replaced with initz In Essential LF90, the concept of BOZ values (but not the Fortran 90 syntax) exists in input/output but, because the DATA statement has been removed, there is no place in the source language BOZ constants may appear. Please report any errors to: Technical Support Lahey Computer Systems, Inc. PO Box 6091 865 Tahoe Blvd. Incline Village, NV 89450 Email to Technical Support 3 As did Appendix D, these syntax rules contains two parts. The first part is an extraction of all syntax rules and constraints in the order in which they appear in the standard. The second part is a cross reference with an entry for each terminal symbol and each nonterminal symbol in the syntax rules. The symbols are sorted alphabetically within three categories: nonterminal symbols that are defined, nonterminal symbols that are not defined, and terminal symbols. 8 Except for those ending with -name, the only undefined nonterminal symbols are letter, digit, special-character, and rep-char. As described in 1.5.2, the following rules are assumed. The letters "xyz" stand for any legal syntactic class phrase: 11 xyz-list is xyz [ , xyz ] ... 12 xyz-name is name 13 scalar-xyz is xyz 14 Constraint: scalar-xyz must be scalar. 15 D.1 Syntax Rules and Constraints. Each of the following sections contains the syntax rules and constraints from one section of the standard; that is, Section D.1.1 contains the rules and constraints from Section 1 of the standard, D.1.2 contains those from Section 2, and so on. Note that Sections 1, 13, and 14 contain no syntax rules. 19 D.1.1 Overview 20 D.1.2 Fortran Terms and Concepts. 21 R201 executable-program is program-unit 22 [ program-unit ] ... 23 R202 program-unit is main-program 24 or external-subprogram 25 or module 26 27 R1101 main-program is program-stmt 28 [ specification-part ] 29 [ execution-part ] 30 [ internal-subprogram-part ] 31 end-program-stmt 32 R203 external-subprogram is function-subprogram 33 or subroutine-subprogram 34 R1215 function-subprogram is function-stmt 35 [ specification-part ] 36 [ execution-part ] 37 [ internal-subprogram-part ] 38 end-function-stmt Page 303 1 R1219 subroutine-subprogram is subroutine-stmt 2 [ specification-part ] 3 [ execution-part ] 4 [ internal-subprogram-part ] 5 end-subroutine-stmt 6 R1104 module is module-stmt 7 [ specification-part ] 8 [ module-subprogram-part ] 9 end-module-stmt 10:12 13 R204 specification-part is [ use-stmt ] ... 14 implicit-part 15 [ declaration-construct ] ... 16 R205 implicit-part is IMPLICIT NONE [ implicit-part-stmt ] ... 18 R206 implicit-part-stmt is parameter-stmt 19 or format-stmt 20:21 22 R207 declaration-construct is derived-type-def 23 or interface-block 24 or type-declaration-stmt 25 or specification-stmt 26 or parameter-stmt 27 or format-stmt 28:29 30 R208 execution-part is executable-construct 31 [ execution-part-construct ] ... 32 R209 execution-part-construct is executable-construct 33 or format-stmt 34:35 36 R210 internal-subprogram-part is contains-stmt 37 internal-subprogram 38 [ internal-subprogram ] ... 39 R211 internal-subprogram is function-subprogram 40 or subroutine-subprogram 41 R212 module-subprogram-part is contains-stmt 42 module-subprogram 43 [ module-subprogram ] ... 44 R213 module-subprogram is function-subprogram 45 or subroutine-subprogram 46 R214 specification-stmt is access-stmt 47 48 Page 304 1: 6 7 or namelist-stmt 8 or optional-stmt 9:11 12 R215 executable-construct is action-stmt 13 or case-construct 14 or do-construct 15 or if-construct 16 or where-construct 17 R216 action-stmt is allocate-stmt 18 or assignment-stmt 19 or backspace-stmt 20 or call-stmt 21 or close-stmt 22 23 24 or cycle-stmt 25 or deallocate-stmt 26 or endfile-stmt 27 or end-function-stmt 28 or end-program-stmt 29 or end-subroutine-stmt 30 or exit-stmt 31 or goto-stmt 32 or if-stmt 33 or inquire-stmt 34 or nullify-stmt 35 or open-stmt 36 or pointer-assignment-stmt 37 38 or read-stmt 39 or return-stmt 40 or rewind-stmt 41 or stop-stmt 42 43 or write-stmt 44:47 48 Constraint: An execution-part-construct must not contain an end-function-stmt, end-program-stmt, or end-subroutine-stmt. Page 305 1 D.1.3 Characters, Lexical Tokens, and Source Form. 2 R301 character is alphanumeric-character 3 or special-character 4 R302 alphanumeric-character is letter 5 or digit 6 or underscore 7 R303 underscore is _ 8 R304 name is letter [ alphanumeric-character ] ... 9 Constraint: The maximum length of a name is 31 characters. 10 R305 constant is literal-constant 11 or named-constant 12 R306 literal-constant is int-lit-constant 13 or real-lit-constant 14 or complex-lit-constant 15 or logical-lit-constant 16 or char-lit-constant 17 18 R307 named-constant is name 19 R308 int-constant is constant 20 Constraint: int-constant must be of type integer. 21 R309 char-constant is constant 22 Constraint: char-constant must be of type character. 23 R310 intrinsic-operator is power-op 24 or mult-op 25 or add-op 26 or concat-op 27 or rel-op 28 or not-op 29 or and-op 30 or or-op 31 or equiv-op 32 R708 power-op is ** 33 R709 mult-op is * 34 or / 35 R710 add-op is + 36 or - 37 R712 concat-op is // 38 R714 rel-op is .EQ. 39 or .NE. 40 or .LT. 41 or .LE. 42 or .GT. 43 or .GE. 44 or == 45 or /= Page 306 1 or < 2 or <= 3 or > 4 or >= 5 R719 not-op is .NOT. 6 R720 and-op is .AND. 7 R721 or-op is .OR. 8 R722 equiv-op is .EQV. 9 or .NEQV. 10 R311 defined-operator is defined-unary-op 11 or defined-binary-op 12 or extended-intrinsic-op 13 R704 defined-unary-op is . letter [ letter ] ... . 14 R724 defined-binary-op is . letter [ letter ] ... . 15 R312 extended-intrinsic-op is intrinsic-operator 16 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-lit-constant. 18 R313 label is digit [ digit [ digit [ digit [ digit ] ] ] ] 19 Constraint: The first digit in a label must be nonzero. 20 D.1.4 Intrinsic and Derived Data Types. 21 R401 signed-digit-string is [ sign ] digit-string 22 R402 digit-string is digit [ digit ] ... 23 R403 signed-int-lit-constant is [ sign ] int-lit-constant 24 R404 int-lit-constant is digit-string [ _ kind-param ] 25 R405 kind-param is digit-string 26 or scalar-int-constant-name 27 R406 sign is + 28 or - 29 Constraint: The value of kind-param must be nonnegative. 30 Constraint: The value of kind-param must specify a representation method that exists on the processor. 31 R407 boz-lit-constant is binary-constant 32 or octal-constant 33 or hex-constant 34 Constraint: A boz-lit-constant may only appear as an input or out- put value under the control of each's FORMAT specifier. 35 R408 binary-constant is digit [ digit ] ... 36 37 Constraint: digit must have one of the values 0 or 1. 38 R409 octal-constant is digit [ digit ] ... 39 Page 307 1 Constraint: digit must have one of the values 0 through 7. 2 R410 hex-constant is hex-digit [ hex-digit ] ... 3 4 R411 hex-digit is digit 5 or A 6 or B 7 or C 8 or D 9 or E 10 or F 11 R412 signed-real-lit-constant is [ sign ] real-lit-constant 12 R413 real-lit-constant is significand [ xpn-letter xpn ] [ _ kind-param ] 13 or digit-string xpn-letter xpn [ _ kind-param ] 14 R414 significand is digit-string . [ digit-string ] 15 or . digit-string 16 R415 xpn-letter is E 17 18 R416 xpn is signed-digit-string 19 Constraint: If both kind-param and xpn-letter are present, xpn-letter must be E. 20 Constraint: The value of kind-param must specify an approximation method that exists on the processor. 22 R417 complex-lit-constant is ( real-part , imag-part ) 23 R418 real-part is signed-int-lit-constant 24 or signed-real-lit-constant 25 R419 imag-part is signed-int-lit-constant 26 or signed-real-lit-constant 27 R420 char-lit-constant is [ kind-param _ ] ' [ rep-char ] ... ' 28 or [ kind-param _ ] " [ rep-char ] ... " 29 Constraint: The value of kind-param must specify a representation method that exists on the processor. 30 R421 logical-lit-constant is .TRUE. [ _ kind-param ] 31 or .FALSE. [ _ kind-param ] 32 Constraint: The value of kind-param must specify a representation method that exists on the processor. 33 R422 derived-type-def is derived-type-stmt 34 [ private-sequence-stmt ] ... 35 component-def-stmt 36 [ component-def-stmt ] ... 37 end-type-stmt 38 R423 private-sequence-stmt is PRIVATE 39 or SEQUENCE 40 R424 derived-type-stmt is TYPE [ , access-spec ] :: type-name 41 Constraint: The same private-sequence-stmt must not appear more than once in a given derived-type-def. 43 Constraint: If SEQUENCE is present, all derived types specified in component definitions must be sequence types. Page 308 1 Constraint: An access-spec (5.1.2.2) or a PRIVATE statement within the definition is permitted only if the type definition is within the specification part of a module. 3 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. 5 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-name. 7 R425 end-type-stmt is END TYPE type-name 8 Constraint: The type-name must be the same as that in the corresponding derived-type-stmt. 10 R426 component-def-stmt is type-spec [ [ , component-attr- spec-list ] :: ] component-decl-list 12 R427 component-attr-spec is POINTER 13 or DIMENSION ( component-array-spec ) 14 Constraint: No component-attr-spec may appear more than once in a given component-def-stmt. 15 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. 17 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 includ- ing the type being defined. 20 R428 component-array-spec is explicit-shape-spec-list 21 or deferred-shape-spec-list 22 R429 component-decl is component-name [ ( component-array-spec ) ] [ * char-length ] 24 Constraint: If the POINTER attribute is not specified, each compon- ent-array-spec must be an explicit-shape-spec-list. 26 Constraint: If the POINTER attribute is specified, each component- -array-spec must be a deferred-shape-spec-list. 28 Constraint: The * char-length option is permitted only to the right of the :: when the type specifier is character and not when the length has been declared to the left of the double colon. Constraint: When component-attr-spec is DIMENSION, then component- array-spec must not appear to the left of the double colon. 29 Constraint: A char-length in a component-decl must be a constant specification expression (7.1.6.2). 30 Constraint: Each bound in the explicit-shape-spec (R428) must be a constant specification expression (7.1.6.2). 32 R430 structure-constructor is type-name ( expr-list ) 33 R431 array-constructor is (/ ac-value-list /) 34 R432 ac-value is expr 35 or ac-implied-do 36 R433 ac-implied-do is ( ac-value-list , ac-implied-do-control ) 37 R434 ac-implied-do-control is ac-do-variable = scalar-int-expr , 38 scalar-int-expr [ , scalar-int-expr ] 39 R435 ac-do-variable is scalar-int-variable 40 Constraint: ac-do-variable must be a named variable. 41 Constraint: Each ac-value expression in the sequence must have the same type and type parameters. Page 309 1 D.1.5 Data Object Declarations and Specifications. 2 R501 type-declaration-stmt is type-spec [ , attr-spec ] ... :: entity-decl-list 3 R502 type-spec is INTEGER [ kind-selector ] 4 or REAL [ kind-selector ] 5 6 or COMPLEX [ kind-selector ] 7 or CHARACTER [ char-selector ] 8 or LOGICAL [ kind-selector ] 9 or TYPE ( type-name ) 10 R503 attr-spec is PARAMETER 11 or access-spec 12 or ALLOCATABLE 13 or DIMENSION ( array-spec ) 14 15 or INTENT ( intent-spec ) 16 17 or OPTIONAL 18 or POINTER 19 or SAVE 20 or TARGET 21 R504 entity-decl is object-name [ ( array-spec ) ] [* char-length ] [ = initialization-expr ] or function-name [ ( array- spec ) ] [ * char-length ] 24 R505 kind-selector is ( [ KIND = ] scalar-int- initialization-expr ) 25 Constraint: The same attr-spec must not appear more than once in a given type-declaration-stmt. 26 Constraint: The function-name must be the name of an external function, an intrinsic function, or a function dummy procedure. 28 Constraint: The = initialization-expr must appear if the statement contains a PARAMETER attribute (5.1.2.1). 30 Constraint: If = initialization-expr appears, a double colon separator must appear before the entity-decl-list. 32 Constraint: The = initialization-expr must not appear if object-name is a dummy argument, a function result, an allocatable array, a pointer, an external name, or an automatic object. 36 Constraint: The * char-length option is permitted only to the right of the :: when the type specifier is character and not when the length has been declared to the left of the double colon. 37 Constraint: The ALLOCATABLE attribute may be used only when declaring an array that is not a dummy argument or a function result. 39 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 (5.1.2.4.3). 41 Constraint: An array-spec for a function-name that does not have the pointer attribute must be an explicit-shape-spec-list. 43 Constraint: An array-spec for a function-name that does have the pointer attribute must be a deferred-shape-spec-list. 45 Constraint: If the POINTER attribute is specified, the INTENT attribute must not be specified. Page 310 1 Constraint: If the TARGET attribute is specified, the PARAMETER attribute must not be specified. 3 Constraint: The PARAMETER attribute must not be specified for dummy arguments, pointers, or functions. 5 Constraint: The INTENT and OPTIONAL attributes may be specified only for dummy arguments. 6 Constraint: An entity must not have the PUBLIC attribute if its type has the PRIVATE attribute. 7 Constraint: The SAVE attribute must not be specified for an object that is a dummy argument, a procedure, a function result, or an automatic data object. 9:11 12 Constraint: An array must not have both the ALLOCATABLE attribute and the POINTER attribute. 13 Constraint: An entity must not be given explicitly any attribute more than once in a scoping unit. 14 Constraint: The value specified in a kind-selector must be nonnegative. 16 R506 char-selector is length-selector 17 or ( [ LEN= ] type-param-value , 18 [ KIND= ] scalar-int- initialization-expr ) or ( KIND= scalar-int- initialization-expr [ , LEN= type-param-value ] ) 23 R507 length-selector is ( [ LEN = ] type-param-value ) 24 25 R508 char-length is ( type-param-value ) 26 or scalar-int-lit-constant 27:33 34 R509 type-param-value is specification-expr 35 or * 36 Constraint: A function name must not be declared with an asterisk char-length if the function is an internal or module function, array-valued, pointer-valued, or recursive. 38 R510 access-spec is PUBLIC 39 or PRIVATE 40 Constraint: An access-spec attribute may appear only in the specification-part of a module. 41 R511 intent-spec is IN 42 or OUT 43 or IN OUT Page 311 Constraint: The INTENT attribute may appear only in the specifi- cation-part of a subprogram or an interface body (12.3.2.1). 1 Constraint: The INTENT attribute must not be specified for a dummy argument that is a dummy procedure or a dummy pointer. 3 R512 array-spec is explicit-shape-spec-list 4 or assumed-shape-spec-list 5 or deferred-shape-spec-list 6 7 Constraint: The maximum rank is seven. Constraint: assumed-shape-spec-list must be used for dummy argument arrays. 8 R513 explicit-shape-spec is [ lower-bound : ] upper-bound 9 R514 lower-bound is specification-expr 10 R515 upper-bound is specification-expr 11 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. 13 R516 assumed-shape-spec is [ lower-bound ] : 14 R517 deferred-shape-spec is : 15:21 22 R520 optional-stmt is OPTIONAL :: dummy-arg-name-list 23 Constraint: An optional-stmt may occur only in the scoping unit of a subprogram or an interface body. dummy-arg-name-list must be external subroutines. 24 R521 access-stmt is access-spec [ [ :: ] access-id -list ] 25 R522 access-id is use-name 26 or generic-spec 27 Constraint: An access-stmt may appear only in the scoping unit of a module. Only one accessibility statement with an omitted access-id-list is permitted in the scoping unit of a module. 29 Constraint: Each use-name must be the name of a named variable, nonintrinsic procedure, generic procedure, derived type, named constant, or namelist group. 31 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. 34:42 Page 312 1:42 Page 313 1:23 24 R543 namelist-stmt is NAMELIST /namelist-group-name/ 25 namelist-group-object-list 26 [ [ , ] /namelist-group-name/ 27 namelist-group-object-list ] ... 28 R544 namelist-group-object is variable-name 29 Constraint: A namelist-group-object must not be an array dummy argu- ment with nonconstant bounds, a variable with assumed character length, an automatic object, a pointer, of a type that has an ultimate component that is a pointer, an allocatable array, or a subobject of any of the preceding objects. 32 Constraint: If a namelist-group-name has the PUBLIC attribute, no item in the namelist-group-object-list may have the PRIVATE attribute. 34:45 Page 314 1:23 24 D.1.6 Use of Data Objects. 25 R601 variable is scalar-variable-name 26 or array-variable-name 27 or subobject 28 Constraint: array-variable-name must be the name of a data object that is an array. 29 Constraint: array-variable-name must not have the PARAMETER attribute. 30 Constraint: scalar-variable-name must not have the PARAMETER attribute. 31 Constraint: subobject must not be a subobject designator (e.g., a substring) whose parent is a constant. 33 R602 subobject is array-element 34 or array-section 35 or structure-component 36 or substring 37 R603 logical-variable is variable 38 Constraint: logical-variable must be of type logical. 39 R604 default-logical-variable is variable 40 Constraint: default-logical-variable must be of type default logical. 41 R605 char-variable is variable Page 315 1 Constraint: char-variable must be of type character. 2 R606 default-char-variable is variable 3 Constraint: default-char-variable must be of type default character. 4 R607 int-variable is variable 5 Constraint: int-variable must be of type integer. 6 R608 default-int-variable is variable 7 Constraint: default-int-variable must be of type default integer. 8 R609 substring is parent-string ( substring-range ) 9 R610 parent-string is scalar-variable-name 10 or array-element 11 or scalar-structure-component 12 or scalar-constant 13 R611 substring-range is [ scalar-int-expr ] : [ scalar-int-expr ] 14 Constraint: parent-string must be of type character. 15 R612 data-ref is part-ref [ % part-ref ] ... 16 R613 part-ref is part-name [ ( section- subscript-list ) ] 17 Constraint: In a data-ref, each part-name except the rightmost must be of derived type. 18 Constraint: In a data-ref, each part-name except the leftmost must be the name of a component of the derived type defin- ition of the type of the preceding part-name. 20 Constraint: In a part-ref containing a section-subscript-list, the number of section-subscripts must equal the rank of part-name. 22 Constraint: In a data-ref, there must not be more than one part-ref with nonzero rank. 24 R614 structure-component is data-ref 25 Constraint: In a structure-component, there must be more than one one part-ref and the rightmost part-ref must be of the form part-name. 27 R615 array-element is data-ref 28 Constraint: In an array-element, every part-ref must have rank zero and at least one part-ref must contain a subscript-list. 30 R616 array-section is data-ref [ ( substring-range ) ] 31 Constraint: In an array-section, one part-ref must have a section- subscript-list and have nonzero rank. 33 Constraint: In an array-section with a substring-range, the right- most part-name must be of type character. 35 R617 subscript is scalar-int-expr 36 R618 section-subscript is subscript 37 or subscript-triplet 38 or vector-subscript 39 R619 subscript-triplet is [ subscript ] : [ subscript ] [ : stride ] 40 R620 stride is scalar-int-expr Page 316 1 R621 vector-subscript is int-expr 2 Constraint: A vector-subscript must be an integer array expression of rank one. 3:4 5 R622 allocate-stmt is ALLOCATE ( allocation-list 6 [ , STAT= stat-variable ] ) 7 R623 stat-variable is scalar-int-variable 8 R624 allocation is allocate-object [ ( explicit- shape-spec-list ) ] 9 R625 allocate-object is variable-name 10 or structure-component 11 R626 allocate-shape-spec is [ allocate-lower-bound : ] allocate-upper-bound 12 R627 allocate-lower-bound is scalar-int-exp 13 R628 allocate-upper-bound is scalar-int-exp Constraint: Each allocate-object must be a pointer or an allocatable array. Constraint: The number of allocate-shpae-specs in an allocate- shape-spec-list must be the same as the rank of the pointer or allocatable array. 15 R629 nullify-stmt is NULLIFY ( pointer-object-list ) 16 R630 pointer-object is variable-name 17 or structure-component 20 Constraint: Each pointer-object must have the POINTER attribute. 21 R631 deallocate-stmt is DEALLOCATE ( allocate-object- list 22 [ , STAT = stat-variable ] ) 23 Constraint: Each allocate-object must be a pointer or an allocatable array. 24 D.1.7 Expressions and Assignment. 34 R701 primary is constant 35 or constant-subobject 36 or variable 37 or array-constructor 38 or structure-constructor 39 or function-reference 40 or ( expr ) 41 R702 constant-subobject is subobject 42 Constraint: subobject must be a subobject designator whose parent is a constant. 43 Constraint: A variable that is a primary must not be an assumed- size array. 1 R703 level-1-expr is [ defined-unary-op ] primary 2 R704 defined-unary-op is . letter [ letter ] ... . 3 Constraint: A defined-unary-op must not contain more than 31 letters and must not be the same as any intrinsic-operator or logical-lit-constant. 5 R705 mult-operand is level-1-expr [ power-op mult-operand ] 40 R706 add-operand is [ add-operand mult-op ] mult-operand Page 317 1 R707 level-2-expr is [ [ level-2-expr ] add-op ] add-operand 2 R708 power-op is ** 3 R709 mult-op is * 4 or / 5 R710 add-op is + 6 or - 7 R711 level-3-expr is [ level-3-expr concat-op ] level-2-expr 8 R712 concat-op is // 9 R713 level-4-expr is [ level-3-expr rel-op ] level-3-expr 10 R714 rel-op is .EQ. 11 or .NE. 12 or .LT. 13 or .LE. 14 or .GT. 15 or .GE. 16 or == 17 or /= 18 or < 19 or <= 20 or > 21 or >= 22 R715 and-operand is [ not-op ] level-4-expr 23 R716 or-operand is [ or-operand and-op ] and-operand 24 R717 equiv-operand is [ equiv-operand or-op ] or-operand 25 R718 level-5-expr is [ level-5-expr equiv-op ] equiv-operand 26 R719 not-op is .NOT. 27 R720 and-op is .AND. 28 R721 or-op is .OR. 29 R722 equiv-op is .EQV. 30 or .NEQV. 31 R723 expr is [ expr defined-binary-op ] level-5-expr 32 R724 defined-binary-op is . letter [ letter ] ... . 33 Constraint: A defined-binary-op must not contain more than 31 letters and must not be the same as any intrinsic- operator or logical-lit-constant. 35 R725 logical-expr is expr 36 Constraint: logical-expr must be type logical. 37 R726 char-expr is expr 38 Constraint: char-expr must be type character. 39 R727 default-char-expr is expr 40 Constraint: default-char-expr must be of type default character. 41 R728 int-expr is expr Page 318 1 Constraint: int-expr must be type integer. 2 R729 numeric-expr is expr 3 Constraint: numeric-expr must be of type integer, real or complex. 4 R730 initz-expr is expr 5 R731 char-initz-expr is char-expr 6 R732 int-initz-expr is int-expr 7 R733 logical-initz-expr is logical-expr 12 R734 specification-expr is scalar-int-expr 13 Constraint: The scalar-int-expr must be a restricted expression. 14 R735 assignment-stmt is variable = expr 15 16 R736 pointer-assignment-stmt is pointer-object => target 17 R737 target is variable 18 or expr 19 Constraint: The pointer-object must have the POINTER attribute. 20 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 or be a subobject, other than a structure component of an object with the POINTER attribute. 23 Constraint: The target must be of the same type, type parameters, and rank as the pointer. 24 Constraint: The target must not be an array section with a vector subscript. 25 Constraint: The expr must deliver a pointer result. 26 27 R739 where-construct is where-construct-stmt 28 [ assignment-stmt ] ... 29 [ elsewhere-stmt 30 [ assignment-stmt ] ... ] 31 end-where-stmt 32 R740 where-construct-stmt is WHERE ( mask-expr ) 33 R741 mask-expr is logical-expr 34 R742 elsewhere-stmt is ELSEWHERE 35 R743 end-where-stmt is END WHERE 36 Constraint: In each assignment-stmt, the mask-expr and the variable being defined must be arrays of the same shape. 38 Constraint: The assignment-stmt must not be a defined assignment. Page 319 1 D.1.8 Execution Control. 2 R801 block is [ execution-part-construct ] ... 3 R802 if-construct is if-then-stmt 4 block 5 [ else-if-stmt 6 block ] ... 7 [ else-stmt 8 block ] 9 end-if-stmt 10 R803 if-then-stmt is [ if-construct-name : ] IF ( scalar-logical-expr ) THEN 11 R804 else-if-stmt is ELSE IF ( scalar-logical-expr ) THEN [ if-construct-name ] 12 R805 else-stmt is ELSE [ if-construct-name ] 13 R806 end-if-stmt is END IF [ if-construct-name ] 14 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. 19 R807 if-stmt is IF ( scalar-logical-expr ) action-stmt 20 Constraint: The action-stmt in the if-stmt must not be an if-stmt, end-program-stmt, end-function-stmt, or end-subroutine- stmt. 22 R808 case-construct is select-case-stmt 23 [ case-stmt 24 block ] ... 25 end-select-stmt 26 R809 select-case-stmt is [ case-construct-name : ] SELECT CASE ( case-expr ) 27 R810 case-stmt is CASE case-selector [case- construct-name] 28 R811 end-select-stmt is END SELECT [ case-construct- name ] 29 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 correspond- ing 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. 35 R812 case-expr is scalar-int-expr 36 or scalar-char-expr 37 38 R813 case-selector is ( case-value-range-list ) 39 or DEFAULT 40 Constraint: No more than one of the selectors of one of the CASE statements may be DEFAULT. Constraint: The DEFAULT selector must be either the first or last selector. 41 R814 case-value-range is case-value 42 or case-value : 43 or : case-value 44 or case-value : case-value Page 320 1 R815 case-value is scalar-int-initz-expr 2 or scalar-char-initz-expr 3 or scalar-logical-initz-expr 4 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. 7 8 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. 10 R816 do-construct is block-do-construct 11 12 R817 block-do-construct is do-stmt 13 do-block 14 end-do 15 R818 do-stmt is nonlabel-do-stmt 16:17 18 R820 nonlabel-do-stmt is [ do-construct-name : ] DO [ loop-control ] 19 R821 loop-control is do-variable = scalar-numeric- expr , scalar-numeric-expr [ , scalar-numeric-expr ] or WHILE ( scalar-logical-expr ) 22 R822 do-variable is scalar-variable 23 Constraint: The do-variable must be a named scalar variable of type integer. 25 Constraint: Each scalar-numeric-expr in loop-control must be of type integer. 27 R823 do-block is block 28 R824 end-do is end-do-stmt 29 30 R825 end-do-stmt is END DO [ do-construct-name ] 31 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 does not so specify a do-construct-name, the corresponding end-do must not specify a do-construct-name. 35:43 Page 321 1:19 20 R834 cycle-stmt is CYCLE [ do-construct-name ] 21 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. 23 R835 exit-stmt is EXIT [ do-construct-name ] 24 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. 26 R836 goto-stmt is GO TO label 27 Constraint: The label must be the statement label of a branch target statement that appears in the same scoping unit as the goto-stmt. 28:42 Page 322 1:2 3 R842 stop-stmt is STOP [ stop-code ] 4 R843 stop-code is scalar-char-constant 5 or digit [ digit [ digit [ digit [ digit ] ] ] ] 6 Constraint: scalar-char-constant must be of type default character. 7 8 D.1.9 Input/Output Statements. 9 R901 io-unit is external-file-unit 10 11 or internal-file-unit 12 R902 external-file-unit is scalar-int-expr 13 R903 internal-file-unit is default-char-variable 14 Constraint: The char-variable must not be an array section with a vector subscript. 15 R904 open-stmt is OPEN ( connect-spec-list ) 16 R905 connect-spec is [ UNIT= ] external-file-unit 17 or IOSTAT= scalar-default-int-variable 18 or ERR= label 19 or FILE= file-name-expr 20 or STATUS= scalar-default-char-expr 21 or ACCESS= scalar-default-char-expr 22 or FORM= scalar-default-char-expr 23 or RECL= scalar-int-expr 24 25 or POSITION= scalar-default-char-expr 26 or ACTION= scalar-default-char-expr 27 or DELIM= scalar-default-char-expr 28 or PAD= scalar-default-char-expr 29 R906 file-name-expr is scalar-default-char-expr 30 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. 32 Constraint: Each specifier must not appear more than once in a given open-stmt; an external-file-unit must be specified. 34 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. Constraint: THE POSITION= specifier is required in an OPEN statement. 36 R907 close-stmt is CLOSE ( close-spec-list ) 37 R908 close-spec is [ UNIT= ] external-file-unit 38 or IOSTAT= scalar-default-int-variable 39 or ERR= label 40 or STATUS= scalar-default-char-expr 41 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. Page 323 1 Constraint: Each specifier must not appear more than once in a given close-stmt; an external-file-unit must be specified. 38 Constraint: The label used in the ERR= specifier must be the statement label of a branch target 39 statement that appears in the same scoping unit as the CLOSE statement. 40 R909 read-stmt is READ ( io-control-spec-list ) [ input-item-list ] 42 R910 write-stmt is WRITE ( io-control-spec-list ) [ output-item-list ] 43 44 R912 io-control-spec is [ UNIT= ] io-unit 45 or [ FMT= ] format 46 or [ NML= ] namelist-group-name 47 or REC= scalar-int-expr 1 or IOSTAT= scalar-default-int-variable 2 or ERR= label 3 or END= label 4 or ADVANCE= scalar-default-char-expr 5 or SIZE= scalar-default-int-variable 6 or EOR= label 7 Constraint: An io-control-spec-list must contain exactly one io-unit and may contain at most one of each of the other specifiers. 9 Constraint: An END=, EOR=, or SIZE= specifier must not appear in a write-stmt. 10 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. 13 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. 15 Constraint: An io-control-spec-list must not contain both a format and a namelist-group-name. 16 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. 18 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=. 21 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=. 24 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. 26 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 input/output. 29 Constraint: An ADVANCE= specifier may be present only in a formatted sequential input/output statement with explicit format specification (10.1) whose control information list does not contain an internal file unit specifier. 32 Constraint: If an EOR= specifier is present, and ADVANCE= specifier also must appear. 33 R913 format is default-char-expr 34 or label Page 324 1 or * 2 3 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. 5 R914 input-item is variable 6 or io-implied-do 7 R915 output-item is expr 8 or io-implied-do 9 R916 io-implied-do is ( io-implied-do-object-list , io-implied-do-control ) 10 R917 io-implied-do-object is input-item 11 or output-item 12 R918 io-implied-do-control is do-variable = scalar-numeric- expr , scalar-numeric-expr [ , scalar- numeric-expr ] 14 15 Constraint: The do-variable must be a scalar of type integer. 16 Constraint: Each scalar-numeric-expr in an io-implied-do-control must be of type integer. 17 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. 20 R919 backspace-stmt is BACKSPACE( position-spec-list ) 21 22 R920 endfile-stmt is ENDFILE ( position-spec-list ) 23 24 R921 rewind-stmt is REWIND ( position-spec-list ) 25 26 R922 position-spec is [ UNIT = ] external-file-unit 27 or IOSTAT = scalar-default-int- variable 28 or ERR = label 29 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. 31 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. 33 Constraint: A position-spec-list must contain exactly one external- file-unit and may contain at most one of each of the other specifiers. 35 R923 inquire-stmt is INQUIRE ( inquire-spec-list ) 36 or INQUIRE ( IOLENGTH = scalar-default-int-variable ) output-item-list 38 R924 inquire-spec is [ UNIT = ] external-file-unit 39 or FILE = file-name-expr 40 or IOSTAT = scalar-default-int- variable 41 or ERR = label 42 or EXIST = scalar-default-logical- variable 43 or OPENED = scalar-default- logical-variable 44 or NUMBER = scalar-default-int- variable 45 or NAMED = scalar-default-logical- variable Page 325 1 or NAME = scalar-default-char-variable 2 or ACCESS = scalar-default-char-variable 3 or SEQUENTIAL = scalar-default-char-variable 4 or DIRECT = scalar-default-char-variable 5 or FORM = scalar-default-char-variable 6 or FORMATTED = scalar-default-char-variable 7 or UNFORMATTED = scalar-default-char-variable 8 or RECL = scalar-default-int-variable 9 or NEXTREC = scalar-default-int-variable 10 11 or POSITION = scalar-default-char-variable 12 or ACTION = scalar-default-char-variable 13 or READ = scalar-default-char-variable 14 or WRITE = scalar-default-char-variable 15 or READWRITE = scalar-default-char-variable 16 or DELIM = scalar-default-char-variable 17 or PAD = scalar-default-char-variable 18 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. 20 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. 23 D.1.10 Input/Output Editing. 24 R1001 format-stmt is FORMAT format-specification 25 R1002 format-specification is ( format-item-list ) 26 Constraint: The format-stmt must be labeled. 27 Constraint: The comma used to separate format-items in a format- item-list is omitted as follows: 28:29 30 (2) Before a slash edit descriptor 31 32 (3) After a slash edit descriptor 33 (4) Before or after a colon edit descriptor 34 R1003 format-item is [ r ] data-edit-desc 35 or control-edit-desc 36 or char-string-edit-desc 37 or [ r ] ( format-item-list ) 38 R1004 r is int-lit-constant 39 Constraint: r must be positive. 40 Constraint: r must not have a kind parameter specified for it. 41 R1005 data-edit-desc is I w [ . m ] 42 or B w [ . m ] 43 or O w [ . m ] 44 or Z w [ . m ] 45 or F w . d Page 326 1 or E w . d [ E e ] 2 or EN w . d [ E e ] 3 or ES w . d [ E e ] 4 or G w . d [ E e ] 5 or L w 6 or A [ w ] 7 8 R1006 w is int-literal-constant 9 R1007 m is int-literal-constant 10 R1008 d is int-literal-constant 11 R1009 e is int-literal-constant 12 Constraint: w and e must be positive. 13 Constraint: w, m, d, and e must not have kind parameters specified for them. 14 R1010 control-edit-desc is position-edit-desc 15 or / 16 or : 17 or sign-edit-desc 18:21 22 R1012 position-edit-desc is T n 23 or TL n 24 or TR n 25 26 R1013 n is int-literal-constant 27 Constraint: n must be positive. 28 Constraint: n must not have a kind parameter specified for it. 29 R1014 sign-edit-desc is SP 30 or SS 31:33 34 R1016 char-string-edit-desc is char-literal-constant 35:39 40 Constraint: The char-literal-constant must not have a kind parameter specified for it. Page 327 1 D.1.11 Program Units. 2 R1101 main-program is [ program-stmt ] 3 [ specification-part ] 4 [ execution-part ] 5 [ internal-subprogram-part ] 6 end-program-stmt 7 R1102 program-stmt is PROGRAM program-name 8 R1103 end-program-stmt is END PROGRAM program-name 9 Constraint: In a main-program, the execution-part must not contain a RETURN statement. 11 Constraint: The program-name must be identical to the program-name specified in the program-stmt. 14 Constraint: An automatic object must not appear in the specification-part (R204) of a main program. 15 R1104 module is module-stmt 16 [ specification-part ] 17 [ module-subprogram-part ] 18 end-module-stmt 19 R1105 module-stmt is MODULE module-name 20 R1106 end-module-stmt is END MODULE module-name 21 Constraint: The module-name in the end-module-stmt, must be identical to the module-name specified in the module- * stmt. 25 Constraint: An automatic object must not appear in the specification-part (R204) of a module. 26 R1107 use-stmt is USE module-name [ , rename- list ] 27 or USE module-name , ONLY : [ only-list ] 28 R1108 rename is local-name => use-name 29 R1109 only is access-id 30 or [ local-name => ] use-name 31 Constraint: Each access-id must be a public entity in the module. 32 Constraint: Each use-name must be the name of a public entity in the module. 33:43 Page 328 1:4 5 D.1.12 Procedures. 6 R1201 interface-block is interface-stmt 7 [ interface-body ] ... 8 [ module-procedure-stmt ] ... 9 end-interface-stmt 10 R1202 interface-stmt is INTERFACE [ generic-spec ] 11 R1203 end-interface-stmt is END INTERFACE 12 R1204 interface-body is function-stmt 13 [ specification-part ] 44 end-function-stmt 15 or subroutine-stmt 16 [ specification-part ] 17 end-subroutine-stmt 18 R1205 module-procedure-stmt is MODULE PROCEDURE procedure- name-list 19 R1206 generic-spec is generic-name 20 or OPERATOR ( defined-operator ) 21 or ASSIGNMENT ( = ) 22 Constraint: An interface-body must not contain a format-stmt. 23 24 Constraint: The MODULE PROCEDURE specification is allowed only if the interface-block has a generic-spec and has a host that is a module or accesses a module by use association; each procedure-name must be the name of a module procedure that is accesible in the host. 27 28 Constraint: An interface-block in a subprogram must not contain an interface-body for a procedure defined by that sub- program. 30:32 33 R1209 function-reference is function-name ( [ actual-arg- spec-list ] ) 34 35 R1210 call-stmt is CALL subroutine-name ( [ actual-arg-spec-list ] ) 36 R1211 actual-arg-spec is [ keyword = ] actual-arg 37 R1212 keyword is dummy-arg-name 38 R1213 actual-arg is expr 39 or variable 40 or procedure-name 41 42 Page 329 1 Constraint: The keyword = must not appear if the interface of the procedure is implicit in the scoping unit. 3 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. 5 Constraint: Each keyword must be the name of a dummy argument in the explicit interface of the procedure. 7 Constraint: A procedure-name actual-arg must not be the name of an internal procedure and must not be the generic name of a procedure (12.3.2.1, 13.1). 9:10 11 R1215 function-subprogram is function-stmt 12 [ specification-part ] 13 [ execution-part ] 14 [ internal-subprogram-part ] 15 end-function-stmt 16 R1216 function-stmt is [ prefix ] FUNCTION function- name ( [ dummy-arg-name-list ] ) [ RESULT ( result-name ) ] 18 Constraint: The function-name, if different from the result-name, must not appear in any specification statement in the scoping unit of the function subprogram. 20 R1217 prefix is RECURSIVE 21 22 R1218 end-function-stmt is END FUNCTION function-name 23 Constraint: If RESULT is specified, result-name must not be the same as function-name. 24 Constraint: FUNCTION must be present on the end-function-stmt of an internal or module function. 25 26 Constraint: An internal function must not contain an internal- subprogram-part. 27 Constraint: The function-name on the end-function-stmt must be identical to the function-name specified in the function-stmt. 29 R1219 subroutine-subprogram is subroutine-stmt 30 [ specification-part ] 31 [ execution-part ] 32 [ internal-subprogram-part ] 33 end-subroutine-stmt 34 R1220 subroutine-stmt is [ RECURSIVE ] SUBROUTINE subroutine-name ( [ dummy-arg-list ] ) 36 R1221 dummy-arg is dummy-arg-name 37 38 R1222 end-subroutine-stmt is END SUBROUTINE subroutine-name 39 Constraint: SUBROUTINE must be present on the end-subroutine-stmt of an internal or module subroutine. 41 42 Constraint: An internal subroutine must not contain an internal- subprogram-part. Page 330 1 Constraint: The subroutine-name on the end-subroutine-stmt must be identical to the subroutine-name specified in the subroutine-stmt. 3:15 16 R1224 return-stmt is RETURN 17 Constraint: The return-stmt must be contained in the scoping unit of a function or subroutine subprogram. 19 20 R1225 contains-stmt is CONTAINS 21:39 40 D.1.13 Intrinsic Procedures. Page 331 1 D.1.14 Scope, Association, and Definition. 2 D.2 Cross References. In the following cross references, all occurrences of scalar-xyz and xyz-list are treated as occurrences of xyz. 5 D.2.1 Nonterminal Symbols That Are Defined. 6 Symbol Defined in Referenced in 7 ac-do-variable R435 R434 8 ac-implied-do R433 R432 9 ac-implied-do-control R434 R433 10 ac-value R432 R431 R433 11 access-id R522 R521 R1109 12 access-spec R510 R424 R503 R521 13 access-stmt R521 R214 14 action-stmt R216 R215 R807 15 16 actual-arg R1213 R1211 17 actual-arg-spec R1211 R1209 R1210 18 add-op R710 R310 R707 19 add-operand R706 R706 R707 20 21 allocate-lower-bound R627 R626 22 allocate-object R625 R624 R631 23 allocate-shape-spec R626 R624 24 allocate-stmt R622 R216 25 allocate-upper-bound R628 R626 26 allocation R624 R622 27 alphanumeric-character R302 R301 R304 28 29 and-op R720 R310 R716 30 and-operand R715 R716 31 32 array-constructor R431 R701 33 array-element R615 R602 R610 34 array-section R616 R602 35 array-spec R512 R503 R504 36 37 38 assignment-stmt R735 R216 R739 39 assumed-shape-spec R516 R512 40 41 attr-spec R503 R501 42 backspace-stmt R919 R216 43 binary-constant R408 R407 44 45 block R801 R802 R808 R823 46 47 48 block-do-construct R817 R816 49 boz-lit-constant R407 R306 Page 332 Symbol Defined in Referenced in 1 2 call-stmt R1210 R216 3 case-construct R808 R215 4 case-expr R812 R809 5 case-selector R813 R810 6 case-stmt R810 R808 7 case-value R815 R814 8 case-value-range R814 R813 9 char-constant R309 R843 10 char-expr R726 R731 R812 11 char-initz-expr R731 R815 12 char-length R508 R429 R504 R507 13 char-lit-constant R420 R306 R1016 14 char-selector R506 R502 15 char-string-edit-desc R1016 R1003 16 char-variable R605 17 character R301 18 close-spec R908 R907 19 close-stmt R907 R216 20 21 22 complex-lit-constant R417 R306 23 component-array-spec R428 R427 R429 24 component-attr-spec R427 R426 25 component-decl R429 R426 26 component-def-stmt R426 R422 27 28 concat-op R712 R310 R711 29 connect-spec R905 R904 30 constant R305 R309 R610 R701 31 constant-subobject R702 R701 32 contains-stmt R1225 R210 R212 33 34 control-edit-desc R1010 R1003 35 cycle-stmt R834 R216 36 d R1008 37 data-edit-desc R1003 38 39 40 41 data-ref R612 R614 R615 R616 42 43 44 45 46 47 48 deallocate-stmt R631 R216 49 declaration-construct R207 R204 50 default-char-expr R727 R905 R906 R908 R912 R913 51 default-char-variable R606 R903 R924 52 default-int-variable R608 R905 R908 R912 R913 R922 53 R923 R924 Page 333 Symbol Defined in Referenced in 1 default-logical-variable R604 R924 2 deferred-shape-spec R517 R428 R512 3 defined-binary-op R724 R311 R723 4 defined-operator R311 R1206 5 defined-unary-op R704 R311 R703 6 derived-type-def R422 R207 7 derived-type-stmt R424 R422 8 digit-string R402 R401 R404 R405 R413 R414 9 10 do-block R823 R817 11 12 do-construct R816 R215 13 do-stmt R818 R817 14 15 16 do-variable R822 R821 R918 17 dummy-arg R1221 R1220 18 e R1009 R1005 19 else-if-stmt R804 R802 20 else-stmt R805 R802 21 elsewhere-stmt R742 R739 22 23 end-do R824 R817 24 end-do-stmt R825 R824 25 end-function-stmt R1218 R216 R1204 R1215 26 end-if-stmt R806 R802 27 end-interface-stmt R1203 R1201 28 end-module-stmt R1106 R1104 29 end-program-stmt R1103 R216 R1101 30 end-select-stmt R811 R808 31 end-subroutine-stmt R1222 R216 R1204 R1219 32 end-type-stmt R425 R422 33 end-where-stmt R743 R739 34 endfile-stmt R920 R216 35 entity-decl R504 R501 36 37 equiv-op R722 R310 R718 38 equiv-operand R717 R717 R718 39 40 41 42 executable-construct R215 R208 R209 43 executable-program R201 44 execution-part R208 R1101 R1215 R1219 45 execution-part-construct R209 R208 R801 46 exit-stmt R835 R216 47 explicit-shape-spec R513 R428 R512 R624 48 exponent (xpn) R416 R413 49 exponent-letter (xpn-letter)R415 R413 50 expr R723 R430 R432 R701 R723 51 R725 R726 R727 R728 52 R729 R730 R735 R737 R915 R1213 53 extended-intrinsic-op R312 R311 Page 334 Symbol Defined in Referenced in 1 external-file-unit R902 R901 R905 R908 R919 2 R920 R921 R922 R924 3 4 external-subprogram R203 R202 5 file-name-expr R906 R905 R924 6 format R913 R909 R912 7 format-item R1003 R1002 R1003 8 format-specification R1002 R1001 9 format-stmt R1001 R206 R207 R209 10 function-reference R1209 R701 11 function-stmt R1216 R1204 R1215 12 function-subprogram R1215 R203 R211 R213 13 generic-spec R1206 R522 R1202 14 goto-stmt R836 R216 15 hex-constant R410 R407 16 hex-digit R411 R410 17 if-construct R802 R215 14 if-stmt R807 R216 15 if-then-stmt R803 R802 16 imag-part R419 R417 17 implicit-part R205 R204 18 implicit-part-stmt R206 R205 19 20 21 initz-expr R730 R504 22 23 input-item R914 R909 R917 24 inquire-spec R924 R923 25 inquire-stmt R923 R216 26 27 int-expr R728 R434 R611 R617 28 R620 R621 R732 R734 29 R812 R902 R905 R912 R1224 30 int-initz-expr R732 R505 R506 R815 31 int-lit-constant R404 R306 R403 R508 R1004 32 R1006 R1007 R1008 R1009 33 int-variable R607 R435 R623 34 intent-spec R511 R503 35 36 interface-block R1201 R207 37 interface-body R1204 R1201 38 interface-stmt R1202 R1201 39 internal-file-unit R903 R901 40 internal-subprogram R211 R210 41 internal-subprogram-part R210 R1101 R1215 R1219 42 intrinsic-operator R310 R312 43 44 io-control-spec R912 R909 R910 45 io-implied-do R916 R914 R915 46 io-implied-do-control R918 R916 47 io-implied-do-object R917 R916 48 io-unit R901 R912 Page 335 Symbol Defined in Referenced in 1 2 keyword R1212 R1211 3 kind-param R405 R404 R413 R420 R421 4 kind-selector R505 R502 5 label R313 R836 R905 R908 R912 6 R913 R922 R924 7 8 9 length-selector R507 R506 10 11 level-1-expr R703 R705 12 level-2-expr R707 R707 R711 13 level-3-expr R711 R711 R713 14 level-4-expr R713 R715 15 level-5-expr R718 R718 R723 16 lit-constant R306 R305 17 logical-expr R725 R733 R741 R803 R804 18 R807 R812 R821 19 logical-initz-expr R733 R815 20 logical-lit-constant R421 R306 21 logical-variable R603 22 loop-control R821 R820 23 lower-bound R514 R513 R516 24 m R1007 R1005 25 main-program R1101 R202 26 mask-expr R741 R740 27 module R1104 R202 28 module-procedure-stmt R1205 R1201 29 module-stmt R1105 R1104 30 module-subprogram R213 R212 31 module-subprogram-part R212 R1104 32 mult-op R709 R310 R706 33 mult-operand R705 R705 R706 34 n R1013 R1012 35 name R304 R307 36 named-constant R307 R305 37 38 namelist-group-object R544 R543 39 namelist-stmt R543 R214 40 41 nonlabel-do-stmt R820 R818 42 not-op R719 R310 R715 43 nullify-stmt R626 R216 44 numeric-expr R729 R821 R918 45 octal-constant R409 R407 46 only R1109 R1107 47 open-stmt R904 R216 48 optional-stmt R520 R214 49 or-op R721 R310 R717 50 or-operand R716 R716 R717 51 52 output-item R915 R910 R917 R923 53 Page 336 Symbol Defined in Referenced in 1 parent-string R610 R609 2 part-ref R613 R612 3 4 pointer-assignment-stmt R736 R216 5 pointer-object R627 R626 R736 6 7 position-edit-desc R1012 R1010 8 position-spec R922 R919 R920 R921 9 power-op R708 R310 R705 10 prefix R1217 R1216 11 primary R701 R703 12 13 private-sequence-stmt R423 R422 14 program-stmt R1102 R1101 15 program-unit R202 R201 16 r R1004 R1003 6 read-stmt R909 R216 7 real-lit-constant R413 R306 R412 8 real-part R418 R417 9 rel-op R714 R310 R713 10 rename R1108 R1107 11 return-stmt R1224 R216 12 rewind-stmt R921 R216 13 14 15 section-subscript R618 R613 16 select-case-stmt R809 R808 17 18 sign R406 R401 R403 R412 19 sign-edit-desc R1014 R1010 20 signed-digit-string R401 R416 21 signed-int-lit-constant R403 R418 R419 22 signed-real-lit-constant R412 R418 R419 23 significand R414 R413 24 specification-expr R734 R509 R514 R515 25 specification-part R204 R1101 R1104 R1204 R1215 26 R1219 27 specification-stmt R214 R207 28 stat-variable R623 R622 R631 29 30 stop-code R843 R842 31 stop-stmt R842 R216 32 stride R620 R619 33 structure-component R614 R602 R610 R625 R627 34 structure-constructor R430 R701 35 subobject R602 R601 R702 36 subroutine-stmt R1220 R1204 R1219 37 subroutine-subprogram R1219 R203 R211 R213 38 subscript R617 R618 R619 39 subscript-triplet R619 R618 40 substring R609 R602 41 substring-range R611 R609 R616 42 target R737 R736 Page 337 Symbol Defined in Referenced in 1 2 type-declaration-stmt R501 R207 3 type-param-value R509 R506 R507 R508 4 type-spec R502 R426 R501 R1217 5 underscore R303 R302 6 upper-bound R515 R513 7 use-stmt R1107 R204 8 variable R601 R603 R604 R605 R606 9 R607 R608 R701 R735 10 R737 R822 R914 R1213 11 vector-subscript R621 R618 12 w R1006 R1005 13 where-construct R739 R215 14 where-construct-stmt R740 R739 15 16 write-stmt R910 R216 17 D.2.2 Nonterminal Symbols That Are Not Defined. 18 array-name R526 19 array-variable-name R601 20 21 case-construct-name R809 R810 R811 22 23 component-name R429 24 digit R302 R313 R402 R408 25 R409 R411 R843 26 do-construct-name R820 R825 R834 R835 27 28 dummy-arg-name R520 R1212 R1216 R1221 29 30 31 function-name R504 R1209 R1216 R1218 32 generic-name R1206 33 if-construct-name R803 R804 R805 R806 34 int-constant-name R405 35 36 letter R302 R304 R704 R724 37 local-name R1108 R1109 38 module-name R1105 R1106 R1107 39 namelist-group-name R543 R912 26 object-name R504 27 part-name R613 28 procedure-name R1205 R1213 29 program-name R1102 R1103 30 rep-char R420 R1016 31 result-name R1216 32 special-character R301 33 subroutine-name R1210 R1220 R1222 34 type-name R424 R425 R430 R502 35 use-name R522 R1108 R1109 36 variable-name R544 R601 R610 R625 37 R627 Page 338 Symbol Defined in Referenced in 1 D.2.3 Terminal Symbols. 2 % R612 3 ' R408 R409 R410 R420 4 ( R417 R427 R429 R430 R433 R502 R503 R504 R505 R506 R507 R508 R609 R613 R616 R622 R624 R626 R631 R701 R740 R803 R804 R807 R809 R813 R821 R904 R907 R909 R910 R916 R919 R920 R921 R923 R1002 R1003 R1206 R1209 R1210 R1216 R1220 16 (/ R431 17 ) R417 R427 R429 R430 R433 R502 R503 R504 R505 R506 R507 R508 R609 R613 R616 R622 R624 R626 R631 R701 R740 R803 R804 R807 R809 R813 R821 R904 R907 R909 R910 R916 R919 R920 R921 R923 R1002 R1003 R1206 R1209 R1210 R1216 R1220 29 * R429 R504 R507 R509 R709 R901 R913 R1221 32 ** R708 33 + R406 R710 34 , R417 R424 R426 R433 R434 R501 R506 R507 R543 R622 R631 R821 R909 R916 R918 R1107 24 - R406 R710 25 . R414 R704 R724 R1005 26 .AND. R720 27 .EQ. R714 28 .EQV. R722 29 .FALSE. R421 30 .GE. R714 31 .GT. R714 32 .LE. R714 33 .LT. R714 34 .NE. R714 35 .NEQV. R722 Page 339 Symbol Defined in Referenced in 1 .NOT. R719 2 .OR. R721 3 .TRUE. R421 4 / R543 R709 R1010 5 6 /) R431 7 // R712 8 /= R714 9 : R513 R516 R517 R611 10 R619 R803 R809 R814 11 R820 R1010 R1107 12 :: R424 R426 R501 R520 13 R5211 14 15 < R714 16 <= R714 17 = R434 R504 R505 R507 18 R622 R631 R735 R821 19 R918 R922 R923 R924 R1206 20 R1211 21 22 == R714 23 => R736 R1108 R1109 24 > R714 25 >= R714 26 A R411 R1005 27 ACCESS R905 R924 28 ACTION R905 R924 29 ADVANCE R912 30 ALLOCATABLE R503 R526 31 ALLOCATE R622 32 33 ASSIGNMENT R1206 34 B R408 R411 R1005 35 BACKSPACE R919 36 37 38 39 40 C R411 41 CALL R1210 42 CASE R809 R810 43 CHARACTER R502 44 CLOSE R907 45 46 COMPLEX R502 47 CONTAINS R1225 48 49 CYCLE R834 50 D R411 51 52 DEALLOCATE R631 53 DEFAULT R813 Page 340 Symbol Defined in Referenced in 1 DELIM R905 R924 2 DIMENSION R427 R503 3 DIRECT R924 4 DO R820 R825 5 6 E R411 R415 R1005 7 ELSE R804 R805 8 ELSEWHERE R742 9 EN R1005 10 END R425 R743 R806 R811 11 R825 R912 R1103 R1106 12 R1203 R1218 R1222 13 ENDFILE R920 14 15 EOR R912 16 17 ERR R905 R908 R912 R922 R924 18 ES R905 R1005 19 EXIST R924 20 EXIT R835 21 22 F R411 R1005 23 FILE R905 R924 24 FMT R912 25 FORM R905 R924 26 FORMAT R1001 27 FORMATTED R924 28 FUNCTION R1216 R1218 29 G R1005 30 GO R836 14 15 I R1005 16 IF R803 R804 R806 R807 17 IMPLICIT R205 18 IN R511 19 IN OUT R511 20 INQUIRE R923 21 INTEGER R502 22 INTENT R503 23 INTERFACE R1202 R1203 24 25 IOLENGTH R923 27 IOSTAT R905 R908 R912 R922 R924 29 KIND R505 R506 30 L R1005 32 LEN R506 R507 33 LOGICAL R502 34 MODULE R1105 R1106 R1205 35 NAME R924 36 NAMED R924 37 NAMELIST R543 38 NEXTREC R924 39 NML R912 Page 341 Symbol Defined in Referenced in 1 NONE R205 2 NULLIFY R626 3 NUMBER R924 4 O R409 R1005 5 ONLY R1107 6 OPEN R904 7 OPENED R924 8 OPERATOR R1206 9 OPTIONAL R503 R520 10 OUT R511 50 51 PAD R905 R924 53 PARAMETER R503 54 55 POINTER R427 R503 56 POSITION R905 R924 2 3 4 PRIVATE R423 R510 5 PROCEDURE R1205 6 PROGRAM R1102 R1103 7 PUBLIC R510 8 READ R909 R924 9 READWRITE R924 10 REAL R502 11 REC R912 12 RECL R924 R924 14 RECURSIVE R1217 R1220 15 RESULT R1216 16 RETURN R1224 17 REWIND R921 18 19 SAVE R503 20 SELECT R809 R811 21 SEQUENCE R423 22 SEQUENTIAL R924 23 SIZE R912 24 SP R1014 25 SS R1014 26 STAT R622 R631 27 STATUS R905 R908 28 STOP R842 29 SUBROUTINE R1220 R1222 30 T R1012 31 TARGET R503 32 THEN R803 R804 33 TL R1012 34 TO R836 35 TR R1012 36 TYPE R424 R425 R502 37 UNFORMATTED R924 39 UNIT R905 R908 R912 R922 R924 40 USE R1107 Page 342 Symbol Defined in Referenced in 1 WHERE R739 R740 R743 2 WHILE R821 3 WRITE R910 R924 4 5 Z R410 R1005 6 _ R303 R404 R413 R420 R421 Return to Lahey home page |