(j3.2006) J3 Fortran interp letter ballot #13 - due 17-Aug-2007 ** due 6-Aug-2007 if possible **

Whitlock, Stan stan.whitlock
Mon Jul 16 15:44:27 EDT 2007


 

                                                             J3/07-xxx

 

Date:   16-Jul-2007

To:     J3 Members

From:   interp/Stan Whitlock

Subj:   J3 Fortran interp letter ballot #13 - due 17-Aug-2007

 

****: due 6-Aug-2007 if possible

 

Enclosed in the thirteenth letter ballot on Fortran interpretations.

 

The rules by which we operate say:

 

    o   J3 votes on the answer at a J3 meeting; a simple majority

        vote marks the answer as "passed by J3 meeting".

 

    o   Between J3 meetings the chair of /interp sends a J3 letter

        ballot to J3 to approve interp answers that have been "passed

        by J3 meeting".  The letter ballot runs for 30 days.  Not

        voting on three of four consecutive J3 letter ballots is

        grounds to terminate J3 membership.  An interp answer passes

        by a 2/3rds vote;  a no vote must be accompanied by an

        explanation of the changes necessary to change the member's

        vote to yes.

 

        J3/interp reserves the right to recall an interp answer for

        more study even if the answer passes.

 

9 Fortran 2003 interpretations are currently "Passed by J3 meeting"

after J3 meeting #180.  This is the letter ballot phase to go from

"Passed by J3 meeting" to "Passed by J3 letter ballot".

 

The following Fortran interpretations are being balloted:

 

Yes   No    Number     Title

 

---   ---   F03/0028   Commas in complex namelist output

---   ---   F03/0048   Control edit descriptors in UDDTIO

---   ---   F03/0049   Separators in list-directed output

                        involving UDDTIO

---   ---   F03/0050   Questions about internal files

---   ---   F03/0051   Repeat specifiers and UDDTIO

---   ---   F03/0086   Elemental and BIND(C)

---   ---   F03/0087   Entry names as dummy procedure arguments

---   ---   F03/0088   Defined operations/assignments and

                        VOLATILE/ASYNCHRONOUS

---   ---   F03/0089   Interoperability of non-BIND derived types

---   ---   F03/0090   Polymorphic array constructors

 

The text of these interpretations is attached.  Each interpretation

starts with a row of "-"s.

 

Please mark the above -Y- in the Yes column for "yes", -C- in the Yes

column for "yes with comment", or -N- in the No column for a "no"

answer {be sure to include your reasons with "no"} and send only the

above text {not this entire mail message} with any comments to

 

        j3 at j3-fortran.org

 

by 11:59:59PM, PST, Friday, 17-Aug-2007, in order to be counted.

 

    ** PLEASE NOTE **

 

17-Aug-2007 is the end of 30 days.  The WG5 London/J3 m181 meeting is

6-10-Aug-2007.  In order to process as many completed F2003 interps

as possible into the next F2003 Corrigendum {#3}, please try to get

your ballots posted before 6-Aug-2007.

 

Thanks                         /Stan

 

----------------------------------------------------------------------

 

NUMBER: F03/0048

TITLE: Control edit descriptors in UDDTIO

KEYWORDS: Control edit descriptor

DEFECT TYPE: Erratum

STATUS: Passed by J3 meeting

 

QUESTION:

 

Consider the following program:

 

MODULE m

 

  TYPE t

    INTEGER :: i = 0

  CONTAINS

    PROCEDURE, PRIVATE :: pwf

    GENERIC :: WRITE(FORMATTED) => pwf

  END TYPE

 

CONTAINS

 

  RECURSIVE SUBROUTINE pwf(dtv, unit, iotype, vlist, iostat, iomsg)

    CLASS(t),         INTENT(IN)    :: dtv

    INTEGER,          INTENT(IN)    :: unit

    CHARACTER(LEN=*), INTENT(IN)    :: iotype

    INTEGER,          INTENT(IN)    :: vlist(:)

    INTEGER,          INTENT(OUT)   :: iostat

    CHARACTER(LEN=*), INTENT(INOUT) :: iomsg

    WRITE(unit, '(i1, /)') dtv%i

    WRITE(unit, '(t1, a2)') 'AB'

  END SUBROUTINE pwf

 

END MODULE

 

PROGRAM foo

  USE m

  IMPLICIT NONE

  TYPE(t) :: a

  a%i = 3

  PRINT *, 'xyz', a

end program

 

9.5.3.7.2 states:

  A record positioning edit descriptor, such as TL and TR, used on

  unit by a child data transfer statement shall not cause the record

  position to be positioned before the record position at the time the

  user-defined derived-type input/output procedure was invoked.

 

The term "record position" is used, but it doesn't appear to be

defined anywhere.  Depending on the interpretation, the above program

might be standard-conforming, or it might not be.

 

If "record position" is taken to mean "the position within the current

record", regardless of which record is the current record, then the

record position at the beginning of the UDDTIO procedure is before the

fourth character of the record.  The first child data transfer

statement begins a new record, and the second child data transfer

statement writes to the first character of the new record.  This would

be before the "record position" at the time the UDDTIO procedure was

invoked, and the program would not be standard-conforming.

 

If "record position" is taken to mean a combination of the record and

the position within that record (essentially making it mean the same

thing as "file position"), then the above program is standard-

conforming, since the control edit descriptor doesn't cause the file

to be positioned before the record position when the UDDTIO procedure

was invoked.

 

What is the meaning of "record position", and is the above program

standard-conforming?

 

ANSWER:

 

The term "record position" is not well defined.

 

The intent of 9.5.3.7.2 was to prohibit a child data transfer statement

from possibly overwriting or re-reading any characters in the current

record that an active parent I/O statement had previously written or
read.

9.5.3.7.2 should have used the term "file position" instead of

"record position". 

 

Therefore, the program is standard-conforming, and prints

 xyz.3

AB

 

where the first record starts with a space and the "." represents 0 or

more spaces.

 

Edits are supplied to clarify the intent of 9.5.3.7.2, 

add "file position" to the glossary, and remove the phrases

"record position" and "record positioning" from the standard.

 

EDITS: 

 

[202:34] In section 9.5.3.7.2, in the paragraph that begins with

    "Because a child data transfer statement does not position the

    file prior to data transfer,"

 

replace

    "list item or record positioning edit descriptor" 

with

    "list item or edit descriptor" 

 

 

[202:36] In section 9.5.3.7.2, replace the phrase

    "A record positioning edit descriptor, such as TL and TR,"

with

    "The edit descriptors T and TL,"

 

[463:4]  In section C.6.2, first paragraph, delete "record positioning"

 

[430:4+] In Annex A, add this definition:

  "<<file position>> (9.2.3): A connected unit has a file position.

  A unit's file position typically affects where the next data transfer

  operation will begin transferring data into or out of the file.  The

  file position is usually just before a record, just after a record,

  within a record, just before the first file storage unit in the

  file, just after the last file storage unit in the file, or

  between two adjacent file storage units."

  

SUBMITTED BY: Rob James

 

HISTORY: 05-139    m171  F03/0048 Submitted

         05-139r1  m171  Passed by J3 meeting

         05-170    m172  Failed J3 letter ballot #11

         06-366r2  m178  Passed by J3 meeting

 

----------------------------------------------------------------------

 

NUMBER: F03/0049

TITLE: Separators in list-directed output involving UDDTIO

KEYWORDS: list-directed output, separators, UDDTIO

DEFECT TYPE: Erratum

STATUS: Passed by J3 meeting

 

QUESTION:

 

Consider the following program:

 

MODULE m

  TYPE t

    INTEGER i

  END TYPE

  INTERFACE WRITE(FORMATTED)

    MODULE PROCEDURE formattedWriteT

  END INTERFACE

CONTAINS

  SUBROUTINE formattedWriteT(dtv, unit, iotype, v_list, iostat, iomsg)

    CLASS(t),         INTENT(IN)    :: dtv

    INTEGER,          INTENT(IN)    :: unit

    CHARACTER(LEN=*), INTENT(IN)    :: iotype

    INTEGER,          INTENT(IN)    :: v_list(:)

    INTEGER,          INTENT(OUT)   :: iostat

    CHARACTER(LEN=*), INTENT(INOUT) :: iomsg

 

    WRITE(unit, *) dtv%i, 'a'

  END SUBROUTINE

END MODULE

 

PROGRAM foo

  USE m

  TYPE(t) :: t1 = t(5)

  OPEN(10, FILE='foo.txt', ACCESS='SEQUENTIAL', FORM='FORMATTED', &

       DELIM='NONE')

  WRITE(10, *), 'xyz', t1, 'zyx'

END PROGRAM

 

10.9.2 of Fortran 2003 states that character sequences produced for

list-directed output are not separated from each other by value

separators when the delimiter mode is NONE.  The implication of this

is obvious when the adjacent effective output list items are both of

character type.  But when user-defined derived-type input/output

is involved, it is much less clear whether a separator should be

included in the output.

 

In the example given, it is unclear whether the output should be:

 xyz 5 azyx

or:

 xyz 5 a zyx

 

1. Should a separator be inserted between two non-delimited character

   sequences when one of the character sequences is written by a child

   data transfer statement, and the other is written by a parent data

   transfer statement, where both statements are list-directed?

 

2. Should a separator be inserted between two non-delimited character

   sequences when the character sequences are written by two different

   child data transfer statements, where both statements are

   list-directed?

 

3. Should a separator be inserted between two character sequences when

   one of the character sequences is written by a child data transfer

   statement, and the other is written by a parent data transfer

   statement, where one of the statements is list-directed and the

   other is format-directed?

 

4. Should a separator be inserted between two character sequences when

   the character sequences are written by two different child data

   transfer statements, where one of the statements is list-directed

   and the other is format-directed?

 

ANSWER:

 

1) No. It is the intent of the standard (10.9.2) that when both the

   parent and child data transfer statements are both list-directed

   output statements, or both are namelist output statements, the

   processor treats the first list item appearing in a child data

   transfer statement as if that list item had immediately

   followed the last list item processed by the parent data

   transfer statement, as long as no other data transfers to that

   unit occurred in between the processing of those two list items.

   Therefore, in this case, the two character sequences are

   considered adjacent.

 

2) No. It is the intent of the standard (10.9.2) that when two

   different child data transfer statements are both list-directed

   output statements, or both namelist output statements, they write

   to the same unit, and no other data transfers to that unit occur

   in between the two child data transfer statements, the processor

   treats the first list item appearing in the second child data

   transfer statement as if that list item had immediately followed

   the last list item processed by the first child data transfer

   statement.  Therefore, in this case, the two character sequences

   are considered adjacent.

 

3) It is processor dependent whether or not a separator appears

   between two such character sequences.  In section 10.9.2, the

   phrase "adjacent undelimited character sequences" refers to

   character sequences produced by list directed output.  When one of

   the sequences is written by a child or parent output statement

   that is not list directed, the exception described in the first

   paragraph of 10.9.2 does not apply. The other rules for inserting

   optional blanks around values in list directed output allow the

   processor to insert optional leading and trailing blanks around a

   list item.  The standard does not specify when optional blanks are

   written; therefore, when two adjacent list items (the values

   thereof) are written to an output record, and only one of them was

   written by list directed I/O, the standard does not specify

   whether or not any optional blanks appear between those values in

   the output record.

 

4) It is processor dependent whether or not a separator appears

   between two such character sequences.  See answer 3.

 

EDITS: 

 

[241:5+] In Section 10.9.2, add the following to the end of the

         first paragraph:

  "Two undelimited character sequences are considered adjacent when

   both were written using list directed I/O, no intervening data
transfer

   or I/O file positioning operations occurred, and both were written

   either by a single data transfer statement, or during the execution

   of a parent data transfer statement along with its child data
transfer

   statements."

 

SUBMITTED BY: Rob James

 

HISTORY: 05-140    m171  F03/0049 Submitted

         05-140r1  m171  Passed by J3 meeting

         05-170    m172  Failed J3 letter ballot #11

         06-367r1  m178  Passed by J3 meeting

 

----------------------------------------------------------------------

 

NUMBER: F03/0050

TITLE: Questions about internal files

KEYWORDS: internal file, data transfer

DEFECT TYPE: Interpretation

STATUS: Passed by J3 meeting

 

QUESTIONS:

 

Question 1:

 

Fortran 2003 does not seem to prohibit this kind of recursive internal

I/O.  Was this program intended to be standard-conforming?  If so,

then what does the program print?

 

MODULE m1

  CHARACTER(20) :: ifile = ''

CONTAINS

  CHARACTER(3) FUNCTION foo()

    WRITE(ifile, *) 'QWERTY'

    foo = 'abc'

  END FUNCTION

END MODULE

 

PROGRAM ex1

  USE m1

  WRITE(ifile, *) 'xyz', foo(), 'zyx'

  PRINT *, ifile

END PROGRAM

 

Question 2:

 

Fortran 2003 does not seem to prohibit this kind of recursive internal

I/O.  Was this program intended to be standard-conforming?  If so,

then what does the program print?

 

MODULE m2

  CHARACTER(20) :: ifile = 'abc def ghi jkl mno '

  CHARACTER(3) :: char

CONTAINS

  CHARACTER(3) FUNCTION foo()

    READ(ifile, *) char

    foo = 'abc'

  END FUNCTION

END MODULE

 

PROGRAM ex2

  USE m2

  WRITE(ifile, *) 'xyz', foo(), 'zyx'

  PRINT *, ifile

  PRINT *, char

END PROGRAM

 

Question 3:

 

Fortran 2003 does not appear to prohibit modifying a character

variable when it is being used as an internal file in a data transfer

statement that is currently executing.  Was this program intended to

be standard-conforming?  If so, then what does the program print?

 

MODULE m3

  CHARACTER(20) :: ifile = ''

CONTAINS

  CHARACTER(3) FUNCTION foo()

    ifile = 'bad thing to do?'

    foo = 'abc'

  END FUNCTION

END MODULE

 

PROGRAM ex3

  USE m3

  WRITE(ifile, *) 'xyz', foo(), 'zyx'

  PRINT *, ifile

  PRINT *, flag

END PROGRAM

 

Question 4:

 

Fortran 2003 does not appear to prohibit referencing a character

variable when it is being used as an internal file in a data transfer

statement that is currently executing.  Was this program intended to

be standard-conforming?  If so, then what does the program print?

 

MODULE m4

  CHARACTER(20) :: ifile = ''

  LOGICAL :: flag = .FALSE.

CONTAINS

  CHARACTER(3) FUNCTION foo()

    IF (ifile == ' xyz') THEN

      flag = .TRUE.

    END IF

    foo = 'abc'

  END FUNCTION

END MODULE

 

PROGRAM ex4

  USE m4

  WRITE(ifile, *) 'xyz', foo(), 'zyx'

  PRINT *, ifile

  PRINT *, flag

END PROGRAM

 

ANSWER:

 

All of these examples were intended to be prohibited.  

Edits are provided to prohibit referencing or defining a variable used

as an internal unit as a result of evaluating any output list items, or

transferring values to any input list item.

 

EDITS:

 

In section 9.5.3.4, after the paragraph:

    "If an internal file has been specified, an input/output list item

    shall not be in the file or associated with the file."

    

add these paragraphs [196:29+]:

 

  "During the execution of an output statement that specified an

  internal unit, no part of that internal unit shall be referenced

  or defined as the result of evaluating any output list item. 

  

  During the execution of an input statement that specified an

  internal unit, no part of that internal unit shall be defined

  as the result of transferring a value to any input list item."

 

SUBMITTED BY: Rob James

 

HISTORY: 05-141  m171  F03/0050 Submitted

         06-368  m178  Passed by J3 meeting

 

----------------------------------------------------------------------

 

NUMBER: F03/0051

TITLE: Repeat specifiers and UDDTIO

KEYWORDS: repeat specifier, POS=, UDDTIO

DEFECT TYPE: Erratum

STATUS: Passed by J3 meeting

 

QUESTION:

 

Consider the following program:

 

MODULE m

 

  TYPE t

    INTEGER :: i

    INTEGER :: j

  END TYPE

 

  INTEGER :: ipos

 

  INTERFACE READ(FORMATTED)

    MODULE PROCEDURE formattedReadT

  END INTERFACE

 

CONTAINS

 

  SUBROUTINE formattedReadT (dtv, unit, iotype, vlist, iostat, iomsg)

    CLASS(T), INTENT(INOUT) :: dtv

    INTEGER, INTENT(IN) :: unit

    CHARACTER(*), INTENT(IN) :: iotype

    INTEGER, INTENT(IN) :: vlist(:)

    INTEGER, INTENT(OUT) :: iostat

    CHARACTER(*), INTENT(INOUT) :: iomsg

 

    READ(unit, *) dtv%i

    INQUIRE(unit, POS=ipos)

    READ(unit, *) dtv%j

  END SUBROUTINE

 

END MODULE

 

PROGRAM foo

  USE m

  TYPE(t) :: a

  OPEN(10, FILE='file.txt', ACCESS='stream', FORM='formatted')

  WRITE(10, '(A)') '2*3 5'

  REWIND(10)

  READ(10, *) a

  PRINT *, a%i, a%j, ipos

END PROGRAM

 

10.9 of Fortran 2003 states that the r*c form of list-directed input

is equivalent to r occurrences of c.  So, when the read is performed,

it is as if the input record contains two occurrences of the number 3.

 

The first child read statement reads the first 3, and does not advance

the file position to the next record (because it is a child data

transfer statement).  It appears that the second read statement should

read the second 3.  But the file position between the child read

statements is unclear.

 

What does the above program print?

 

ANSWER:

 

The standard does not specify the behavior of a processor when a list

directed input record contains a r*c constant, and that entire set

of input values is not completely consumed by one list directed

input statement. In particular, the file position for such an input

file when the processor is in the middle of consuming an r*c value,

and a child input statement is invoked, is not defined.  This was an

oversight.  Edits are supplied to prohibit r*c constants in this

case.  The above program is not standard conforming.

 

EDITS:

 

[239:18-] Insert this paragraph just after note 10.28:

    "When the first value of an <r*c> constant is transferred to a list

    item by a list-directed input statement, that input statement shall

    transfer all <r> values of that <r*c> constant to list items before

    causing any child input statement to be invoked.  If that

    list-directed input statement is itself a child input

    statement, it shall transfer all <r> values of that <r*c> constant

    to list items before terminating."

 

SUBMITTED BY: Rob James

 

HISTORY: 05-142    m171  F03/0051 Submitted

         05-142r2  m171  Passed by J3 meeting

         05-170    m172  Failed J3 letter ballot #11

         06-369r1  m178  Passed by J3 meeting

 

----------------------------------------------------------------------

 

NUMBER: F03/0086

TITLE: Elemental and BIND(C)

KEYWORDS: Elemental, BIND(C), ENTRY

DEFECT TYPE: Erratum

STATUS: Passed by J3 meeting

 

QUESTION:

 

 Is it allowed for a procedure to have both the BIND(C) and

 elemental attributes?

 

 Constraint C1242 disallows trivial ways of writing an elemental

 BIND(C) procedure. However, the following example achieves the

 effect for sub_c without violating the syntactic constraint.

 

   elemental subroutine sub(x)

     entry sub_c(x) bind(c)

   end subroutine sub

 

ANSWER:

 

 No, it is not allowed. Constraint C1242 was intended to disallow

 the combination of elemental and BIND(C), but it inadvertently

 failed to cover the case shown in the above example.

 

EDITS

 

 Replace C1242 in subclause 12.5.2.1 with

 "C1242 A procedure shall not have both the ELEMENTAL and BIND

  attributes".

  

SUBMITTED BY: Richard Maine

 

HISTORY: 07-101    m179  Submitted F03/0086

         07-101    m179  Passed by J3 meeting

 

----------------------------------------------------------------------

 

NUMBER: F03/0087

TITLE: Entry names as dummy procedure arguments

KEYWORDS: Entry names, dummy procedure arguments

DEFECT TYPE: Erratum

STATUS: Passed by J3 meeting

 

QUESTION:

 

Does the following subprogram fragment conflict with the 2003 Fortran

standard?  If so, was the conflict intended?

 

  entry A ( X )

    interface

      subroutine X ( A )

        abstract interface

          subroutine I ( ... )

          ...

          end subroutine I

        end interface

        procedure (I) A

      end subroutine X

    end interface

  ...

 

It seems that constraint C1255 in subclause 12.5.2.4 [283:10-12]
prohibits

the entry name A to appear in the PROCEDURE statement in the interface

body.  There shouldn't be a problem, however, since the PROCEDURE

statement is in a different scoping unit.

 

REMARK:

 

There is no constraint parallel to C1255 concerning the
<subroutine-name>

in a SUBROUTINE statement, and only an indirect one (C1235 in subclause

12.5.2.1 [279:24-25]) concerning the <function-name> in a FUNCTION

statement, and only then if the FUNCTION statement has a RESULT clause.

Subclauses 16.1 and 16.2 adequately cover the problems that constraint

C1255 appears to have been intended to cover.

 

ANSWER:

 

It was not intended that this usage be prohibited.  An edit is provided
to

remove the prohibition.

 

EDITS:

 

Within constraint C1255 in subclause 12.5.2.4, insert "the scoping unit

of" after "Within".

 

SUBMITTED BY: Van Snyder

 

HISTORY: 07-105    m179  Submitted F03/0087

         07-105    m179  Passed by J3 meeting

 

----------------------------------------------------------------------

 

NUMBER: F03/0088

TITLE: Defined operations/assignments and VOLATILE/ASYNCHRONOUS

KEYWORDS: Defined operations, defined assignment, VOLATILE,

          ASYNCHRONOUS

DEFECT TYPE: Erratum

STATUS: Passed by J3 meeting

 

PROBLEM:

 

  Fortran 2008 Unresolved Technical issue 097 asked a question that

  also affects Fortran 2003.  Consider this example:

 

          INTERFACE ASSIGNMENT(=)

             SUBROUTINE s(a,b)

                 REAL,INTENT(OUT),VOLATILE :: a(*)

                 REAL,INTENT(IN) :: b(:)

             END SUBROUTINE

          END

          REAL,POINTER :: p(:),q(:)

          ...

          CALL s(p,q)    ! Violation of constraint C1233 [271:9-11],

                         !  associating P with A

          p = q          ! No constraint violation because <actual-arg>

                         !  syntax is not being used

 

QUESTION:

 

  Did Fortran 2003 intend to enforce constraints on <actual-arg> in

  defined assignment?

 

ANSWER:

 

 Yes, the <actual-arg> constraints and restrictions should be enforced

 in defined assignment and in defined operator evaluation.

 

 Edits are provided below to do this.

 

EDITS:

 

  [262:16] add at the end of the paragraph

   " All restrictions and constraints that apply to actual arguments

    in a reference to the function also apply to the corresponding

    operands in the expression as if they were used as actual
arguments."

 

  [263:12] insert after "the second argument."

   " All restrictions and constraints that apply to actual arguments

    in a reference to the subroutine also apply to the left-hand-side

    and to the right-hand-side enclosed in parentheses as if they were

    used as actual arguments."

 

SUBMITTED BY: Stan Whitlock

 

HISTORY: 07-172    m179  Submitted F03/0088 {see 07-171 for F08 fix}

         07-172    m179  Passed by J3 meeting

 

----------------------------------------------------------------------

 

NUMBER: F03/0089

TITLE:  Interoperability of non-BIND derived types

KEYWORDS: Interoperability, derived type

DEFECT TYPE: Erratum

STATUS: Passed by J3 meeting

 

INTRODUCTION

 

Subclause 15.2.3 of 04-007 says [398:9-12]:

 

  "A Fortran derived type is interoperable with a C struct type if the

   derived-type definition of the Fortran type specifies BIND(C)
(4.5.1),

   the Fortran derived type and the C struct type have the same number
of

   components, and the components of the Fortran derived type have types

   and type parameters that are interoperable with the types of the

   corresponding components of the struct type."

 

QUESTIONS

 

  1. Is a Fortran derived type for which BIND(C) is not specified

     interoperable with any C struct type?

 

  2. Does a Fortran derived type interoperate with a C struct type that

     has a different number of components?

 

  3. Does a Fortran derived type interoperate with a C struct type that

     specifies the same components in a different order?

 

  4. Does a Fortran derived type with a pointer or allocatable component

     that has interoperable type and type parameters interoperate with

     any C struct type?

 

ANSWERS:

 

None of these Fortran derived types are interoperable with any C struct
type.

 

EDITS:

 

  [398:9] Replace "if" by "if and only if".

 

SUBMITTED BY: Van Snyder

 

HISTORY: 07-213    m180  Submitted F03/0089

         07-213r2  m180  Passed by J3 meeting

 

----------------------------------------------------------------------

 

NUMBER: F03/0090

TITLE:  Polymorphic array constructors

KEYWORDS: polymorphic, array constructor

DEFECT TYPE: Erratum

STATUS: Passed by J3 meeting

 

QUESTION:

 

Consider

 

  FUNCTION f(dummy,n)

    CLASS(t) dummy

    TYPE(t) f(n)

    f = [ (dummy,i=1,n) ]

  END FUNCTION

 

(1) Is this standard-conforming?

 

(2) If so, is the array constructor polymorphic?

 

ANSWER:

 

(1) Yes.

 

(2) No.  Its declared and dynamic type are both T.

    An edit is provided to clarify this.

 

EDITS:

 

[67:21] "same type" -> "same declared type"

 

[68:9] "type and" -> "declared type and"

 

[68:14+] Insert new paragraph

  "The dynamic type of the array constructor is the same as its declared

   type."

 

SUBMITTED BY: Van Snyder

 

HISTORY:  07-231    m180  Submitted F03/0090 (revised by Malcolm Cohen)

          07-231    m180  Passed by J3 meeting

 

----------------------------------------------------------------------

 

-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://j3-fortran.org/pipermail/j3/attachments/20070716/98c960ac/attachment-0001.html 



More information about the J3 mailing list