(j3.2006) (SC22WG5.5613) Interpretations straw ballot 11

John Reid John.Reid
Sat Dec 19 09:05:16 EST 2015


WG5,

All of those of us that attended the London meeting have goofed over 8 
interpretations that were accepted in J3 votes there. We have not 
processed them further. /INTERP realized this a few days ago and would 
like accelerated processes to be adopted so that the edits can be 
included in Corrigendum 4. With some reluctance, I have agreed. I am 
embarrassed about having said to SC22 in Sept that Corr 4 was nearly 
ready and needed just a final round of checking. /INTERP suggest that 
the new J3 and WG5 ballots be simultaneous. In the hope of finishing by 
the end of Jan, I propose this timetable:

19 Dec Interps ballot 10 ends
19 Dec Interps ballot 11 starts, and is also J3 ballot 35
23 Dec Corr vote ends
9  Jan Interps ballot 11 ends
13 Jan Corr vote starts
27 Jan Corr vote ends
30 Jan Corr sent to SC22

It avoids any more overlapping WG5 ballots and avoids unreasonable 
demands over Christmas and New Year.

Here is the simultaneous ballot. A vote on this by a J3 member will 
count as a J3 vote.

With best wishes for the festive season,

John.
-------------- next part --------------
                                             ISO/IEC JTC1/SC22/WG5 N2091

WG5 straw ballot 11 and J3 letter ballot 35 on Fortran 2008 interpretations
                      John Reid, 19 December 2015

This is the eleventh WG5 vote on a set of draft interpretations for Fortran 
2008. They have all been approved in a J3 meeting vote. This is a simultaneous
WG straw vote and J3 letter ballot. All votes by J3 members will be regarded
as votes in the J3 letter ballot. 

The rules we operate on say:
--- ---
4. The chair of J3/interp gathers all interp answers that are marked
   "passed by J3 letter ballot" and forwards them to the WG5 convenor.
   The WG5 convenor holds a ballot of individual members; a no vote
   must be accompanied by an explanation of the changes necessary to
   change the member's vote to yes. The answers that pass this ballot
   become "WG5 approved".

   J3/interp reserves the right to recall an interp answer for more
   study even if the answer passes.

5. "WG5 approved" answers are processed into a corrigendum document by
   taking the edits from the interp answers and putting them in the
   format required by ISO.  A WG5 vote is made on forwarding the
   corrigendum to SC22.

The following Fortran 2008 interpretations are being balloted:

Yes  No   Number     Title		 
---  --- F08/0128 Is recursive USE within a submodule permitted?
---  --- F08/0138 Type extension in submodules
---  --- F08/0139 Is the name of an external procedure that has a
                  binding label a local identifier?
---  --- F08/0140 Assign to deferred-length coindexed character variable
---  --- F08/0141 Can a statement function have a variable-length PDT
                  result?
---  --- F08/0142 Is useless module extension permitted?
---  --- F08/0143 May a pure procedure have an INTENT(OUT) polymorphic
                  component?
---  --- F08/0144 Is nonadvancing I/O allowed during execution of DO
                  CONCURRENT?
					 
The text of these interpretations is in N2092.  Each interpretation starts 
there 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 to

        sc22wg5 at open-std.org

by 0900 UK time on Saturday, 9 January 2016, in order to be counted.

Thanks,

John.                         
-------------- next part --------------
                                             ISO/IEC JTC1/SC22/WG5 N2092
                                             
Fortran Interpretations waiting for J3 and WG5 ballot, December 17, 2015

                  Stan Whitlock for /interp


======================================================================
Part 1: Interpretation Processing Rules
======================================================================

4. The chair of J3/interp gathers all interp answers that are marked
   "passed by J3 letter ballot" and forwards them to the WG5
   convenor.  The WG5 convenor holds a ballot of individual members;
   a no vote must be accompanied by an explanation of the changes
   necessary to change the member's vote to yes.  The answers that
   pass this ballot become "WG5 approved".

   J3/interp reserves the right to recall an interp answer for more
   study even if the answer passes.

5. "WG5 approved" answers are processed into a corrigendum document
   by taking the edits from the interp answers and putting them in
   the format required by ISO.  A WG5 vote is made on forwarding the
   corrigendum to SC22.  Interps so forwarded are marked
   "Corrigendum".

6. J3/interp creates a edit for the next Fortran Standard if one is
   needed for all interps marked "Corrigendum".


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

NUMBER: F08/0128
TITLE: Is recursive USE within a submodule permitted?
KEYWORDS: SUBMODULE, USE
DEFECT TYPE: Erratum
STATUS: Passed by J3 meeting

QUESTION:

Consider
  Module m1
    Real x
  End Module
  Submodule(m1) subm1
    Use m1
  End Submodule

Q1. The module m1 is referenced from within one of its own
    submodules.  Is this standard-conforming?

Note that the "submodule TR", Technical Report 19767 contains, an edit
with the normative requirement:
  "A submodule shall not reference its ancestor module by use
   association, either directly or indirectly."
along with a note which says
  "It is possible for submodules with different ancestor modules to
   access each other's ancestor modules by use association."
It also contains an edit to insert the direct reference prohibition
as a constraint.

However, none of this text appears in ISO/IEC 1539-1:2010.

The Introduction simply comments that submodules are available, but
not that they have been extended beyond the Technical Report that
created them.

Also, consider

  Module m2
    Real, Private :: a
    Real, Protected :: b
    ...
  End Module
  Submodule(m2) subm2
  Contains
    Subroutine s
      Use m2
      Implicit None
      a = 3
      b = 4
    End Subroutine
  End Submodule

In submodule SUBM2, procedure S references M2 by use association.
Use association does not make "A" accessible.

Q2. Is "A" still accessible by host association?

Also, procedure S attempts to assign a value to B, which is accessed
by use association, but has the PROTECTED attribute.  Normally, this
attribute prevents assignment to variables accessed by use
association.

Q3. Is the assignment to "B" standard-conforming?

DISCUSSION:

The requirement appears in the early drafts of Fortran 2008, up to
08-007r1, then it was modified by paper 08-154r1 creating a UTI
(because the modification was broken), and finally the requirement was
completely removed by paper 09-141.

ANSWER:

A1. No, the example was not intended to be conforming.  Permission for
    a submodule to access its ancestor module by use associated was a
    mistake.  An edit is provided to correct this error.

A2. Moot.

A3. Moot.

EDITS:

[275:9+] 11.2.3 Submodules,
         "A submodule shall not reference its ancestor module by
          use association, either directly or indirectly."
{NOTE TO J3: This could be inserted at [272:23] if that is thought
 to be a better place.}

SUBMITTED BY: Malcolm Cohen

HISTORY: 15-134    m206  F08/0128 submitted
         15-134r1  m206  Revised edits - passed by J3 meeting
         15-187    m207  Failed J3 letter ballot 15-159
         15-208    m207  Revised with 3 options
         15-208    m207  Option 3 passed by J3 meeting

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

NUMBER: F08/0138
TITLE: Type extension in submodules
KEYWORDS: submodules, deferred type-bound procedures
DEFECT TYPE: Clarification
STATUS: Passed by J3 meeting

QUESTION:

Consider the following code:

    module mod_a
      implicit none
      type, abstract :: t_a
       contains
         procedure(p_a), deferred :: p
      end type t_a
      abstract interface
         subroutine p_a(this, q)
           import :: t_a
           class(t_a), intent(inout) :: this
           class(*), intent(in) :: q
         end subroutine
      end interface
    end module mod_a

    submodule(mod_a) imp_p_a
      type, extends(t_a) :: t_imp
         real :: b
      contains
         procedure :: p => psub ! (A)
      end type t_imp
    contains
      subroutine psub(this, q)
        class(t_imp), intent(inout) :: this
        class(*), intent(in) :: q
        ... ! don't care
      end subroutine psub
    end submodule imp_p_a

Constraint C456 in 007r1 reads

"C465 (R448) The procedure-name shall be the name of an accessible
      module procedure or an external procedure that has an explicit
      interface."

Therefore it would appear that statement (A) above is not standard
conforming since PSUB is not the name of a module procedure.

Q1. Is this correct?

If so, extension of a derived type with a deferred type-bound
procedure cannot be done within the specification part of a submodule.

Q2. Was this intended?

ANSWER:

A1. No, this is not correct.  A module procedure is a procedure that
    is defined by a module subprogram (1.3.112.4).  A submodule
    program unit contains a module-subprogram-part (R1116), and this
    contains a (possibly-empty) sequence of module-subprogram's
    (R1107).  Therefore, PSUB is defined by a module subprogram and
    is therefore a module procedure.  Therefore, the statement that
    is commented "(A)" is standard-conforming.

A2. Moot.

EDIT: None.

SUBMITTED BY: R. Bader

HISTORY: 15-160    m207  F08/0138 Submitted
         15-160r1  m207  Revised
         15-160r2  m207  Revised example passed by J3 meeting

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

NUMBER: F08/0139
TITLE: Is the name of an external procedure that has a binding label
       a local identifier?
KEYWORDS: TRANSFER, zero-sized scalar
DEFECT TYPE: Erratum
STATUS: Passed by J3 meeting

QUESTION:

Consider the program fragment:

  Subroutine s() Bind(C,Name='Hello')
      Print *,'Hello'
  End Subroutine
  Subroutine s() Bind(C,Name='World')
    Print *,'World'
  End Subroutine

This does not conform to Fortran 2003, and is not listed as an
extension in the Introduction to Fortran 2008, but the rules for
global names seem to indicate that this is now conforming.

Is this extension deliberate?

ANSWER:

Yes, this was a deliberate change to the Fortran standard.
An edit is provided to mention this in the Introduction.

EDITS:

[xvi] Introduction, paragraph 2, bullet "Programs and procedures",
      append to paragraph
        "The name of an external procedure that has a binding label
         is a local identifier and not a global identifier.".

SUBMITTED BY: Malcolm Cohen

HISTORY: 15-177    m207  F08/0139 submitted - passed by J3 meeting

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

NUMBER: F08/0140
TITLE: Assign to deferred-length coindexed character variable
KEYWORDS: Cobounds, type declaration
DEFECT TYPE: Erratum
STATUS: Passed by J3 meeting

QUESTION:

Q1. Consider the program:

  Program p1
    Type t
      Character(:), Allocatable :: C
    End Type
    Type(t) x[*]
    Allocate ( Character(42) :: x%c )
    Sync All
    If (This_Image()==1) x[2]%c = 'stuff'
  End Program

Is the assignment permitted?

Q2. Consider

  Program p2
    Type t
      Character(:), Pointer :: C
    End Type
    Type(t) x[*]
    Allocate ( Character(42) :: x%c )
    Sync All
    If (This_Image()==1) x[2]%c = 'stuff'
  End Program

ANSWER:

A1. This is not permitted, as it violates the requirement in 7.2.1.2
    Intrinsic assignment statement, paragraph 2, which states that if
    the variable (in an intrinsic assignment statement) is coindexed,
    its deferred length type parameters shall be the same as the
    corresponding type parameters of the expression.

    There is a grammatical error in this requirement; an edit is
    supplied to correct the grammatical error.

A2. This was intended to be permitted, but was inadvertently caught in
    the prohibition that was intended to apply only to allocatable
    variables.  An edit is supplied to correct this error.

EDITS:

[153:25] 7.2.1.2p2, after "coindexed object,", delete "the variable",
[153:26] before "shall not be" insert "the variable",
[153:27] before "shall not have" insert "the variable",
[153:28] change "each"
         to "if the variable is allocatable, each".
making the whole paragraph read

  "If <variable> is a coindexed object,
     - the variable shall not be polymorphic,
     - the variable shall not have an allocatable ultimate component,
       and
     - if the variable is allocatable, each deferred length type
       parameter shall have the same value as the corresponding
       type parameter of <expr>.".

SUBMITTED BY: Van Snyder

HISTORY: 15-161    m207  F08/0140 submitted
         15-161r1  m207  Revised question and answers
         15-161r2  m207  Passed by J3 meeting

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

NUMBER: F08/0141
TITLE: Can a statement function have a variable-length PDT result?
KEYWORDS: Statement function, parameterized derived type
DEFECT TYPE: Erratum
STATUS: Passed by J3 meeting

QUESTION:

Consider

    MODULE m207c006
      TYPE string(n)
        INTEGER,LEN :: n
        CHARACTER(n) :: v
      END TYPE
    END MODULE
    PROGRAM test
      USE m207c006
      CALL s(3)
      CALL s(7)
    CONTAINS
      SUBROUTINE s(n)
        TYPE(string(n)) sf
        TYPE(string(n)) var(3)
        sf(nn) = var(nn)
        var(1) = string(n)('123456789')
        var(2) = string(n)('abcdefgh')
        PRINT *,sf(1),sf(2)
      END SUBROUTINE
    END PROGRAM

If this is conforming, it would appear that the output ought to be
  123abc
  1234567abcdefg

However, for the following reasons, perhaps this is not intended to be
conforming.

(1) A statement function of type character is required to have a
    constant length type parameter.  There is no such requirement on a
    statement function of parameterized derived type.  This seems
    inconsistent, since one can wrap a variable-length character
    in a parameterized derived type.

(2) A statement function is not permitted to invoke a nonintrinsic
    function that requires an explicit interface (and having a PDT
    result requires an explicit interface), nor is it permitted to
    contain a structure constructor.  This would seem to render such a
    statement function almost completely useless, since all it can do
    is to choose between PDT constants or variables, or use an
    intrinsic function such as TRANSFER to construct the result.

(3) Statement functions were declared to be obsolescent long before
    the addition of parameterized derived types to the standard.  It
    has been general policy not to "improve" obsolescent features.
    This would seem to indicate that statement functions were not
    intended to be capable of having parameterized derived type in the
    first place.

Q1. Are statement functions of parameterized derived type intended to
    be conforming?

Q2. If so, are statement functions of parameterized derived type with
    nonconstant length type parameters intended to be conforming?

Q3. If so, is the expected output from the example program above as
    described?

ANSWER:

A1. No, statement functions were not intended to be permitted to be of
    parameterized derived type.  The exception for statement functions
    from the explicit interface requirements was overlooked.  An edit
    is provided to prohibit these.

A2, A3.  Moot.

EDITS:

[22:11+] 1.6.2 Fortran 2003 compatibility, insert new paragraph
  "Fortran 2003 permitted a statement function to be of parameterized
   derived type; this part of ISO/IEC 1539-1 does not permit that."
{Previous corrigenda have already inserted incompatibility
 paragraphs.}

[311:34+] 12.6.4 Statement function, after C1275, insert constraint
  "C1275a A statement function shall not be of a parameterized derived
          type."

SUBMITTED BY: Malcolm Cohen

HISTORY: 15-179    m207  F08/0141 submitted
         15-179r1  m207  Revised edits - passed by J3 meeting

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

NUMBER: F08/0142
TITLE: Is useless module extension permitted?
KEYWORDS: SUBMODULE
DEFECT TYPE: Erratum
STATUS: Passed by J3 meeting
QUESTION:

If a module declares no separate module procedure, it cannot have a
useful submodule as such a submodule has nothing to provide.  Its
module procedures and variables cannot be referenced by any program.

Should useless extension have been prohibited?

ANSWER:

Yes.  Permitting such extension would require the implementation to
export the private details of a module merely for the purpose of
compiling a useless submodule.

An edit is provided to require the ancestor of a submodule to have
declared a separate module procedure.

EDITS:

[275:18] 11.2.3 Submodules, C1113,
         After "shall be the name of a nonintrinsic module"
         insert "that declares a separate module procedure".

SUBMITTED BY: Daniel Chen

HISTORY: 15-209    m207  F08/0142 submitted - passed  by J3 meeting

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

NUMBER: F08/0143
TITLE: May a pure procedure have an INTENT(OUT) polymorphic component?
KEYWORDS: PURE, INTENT(OUT), polymorphic
DEFECT TYPE: Erratum
STATUS: Passed by J3 meeting

QUESTION:

Consider:

  Type t
    Class(*),Allocatable :: c
  End Type
  ...
  Pure Subroutine zap(x)
    Type(t),Intent(Out) x
    x%c = 'I wonder if that invoked an impure procedure?'
  End Subroutine

Is this program standard-conforming?

ANSWER:

No, this is not standard-conforming.

Corrigendum 1 of Fortran 2008 added the constraint
  "C1284a A statement that might result in the deallocation of a
          polymorphic entity is not permitted in a pure procedure."

The type declaration statement with INTENT(OUT) causes the
deallocation of the polymorphic component X%C, and is therefore not
allowed.

However, this is difficult to understand, so a clarifying edit is
provided.

EDITS:

In the constraint added by Corrigendum 1,
  "C1278a An INTENT (OUT) dummy argument of a pure procedure shall not
          be polymorphic."

after the word "polymorphic"
insert "or have a polymorphic allocatable ultimate component".

SUBMITTED BY: Malcolm Cohen

HISTORY: 15-211    m207  F08/0143 submitted - passed by J3 meeting

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

NUMBER: F08/0144
TITLE: Is nonadvancing I/O allowed during execution of DO CONCURRENT?
KEYWORDS: nonadvancing I/O, DO CONCURRENT
DEFECT TYPE: Erratum
STATUS: Passed by J3 meeting

QUESTION:

Consider

  program P
    integer :: I
    do concurrent ( I = 1:10 )
      write ( *, *, advance='NO' ) I
    end do
    write ( *, * )
  end program P

Q1. Is this conforming and if so, what output is produced?

  program Q
    integer :: I
    logical :: L(10) = .FALSE.
    real :: X(10) = 0
    do concurrent ( I = 1:10 )
      if ( mod(i,2) == 0 ) then
        read ( *, '(g15.6)', advance='no' ) X(I)
      else
        read ( *, '(l3)', advance='no' ) L(I)
      end if
    end do
    print *, X, L
  end program

Q2. Is this conforming and what kind of output would be expected?

ANSWER:

No, these programs are not conforming as no interpretation is
established for them.

It was intended that nonadvancing input/output not be permitted within
a DO CONCURRENT construct.

An edit is provided to address this oversight.

[10-007r1:178:18+ at the end of the list in 8.1.6.7p1] insert a list
item:

"  o A DO CONCURRENT construct shall not contain an input/output
     statement that has an ADVANCE= specifier."

SUBMITTED BY: Van Snyder

HISTORY: 15-213    m207  F08/0144 submitted
         15-213r1  m207  Option 2 selected, edit revised - passed by
                          J3 meeting

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






More information about the J3 mailing list