(j3.2006) (SC22WG5.5582) Interps straw ballot 10

John Reid John.Reid
Fri Dec 4 06:24:10 EST 2015


WG5,

Here is interps ballot 10. I am allowing only 14 days this time because 
there are only 5 inteps involved and I told SC22 in Sept. that Corr 4 
was very nearly ready so I am anxious to complete it soon. I hope this 
is acceptable to you.

Best wishes,

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

          WG5 straw ballot 10 on Fortran 2008 interpretations
                      John Reid, 4 December 2015

This is the tenth WG5 vote on a set of draft interpretations for Fortran 
2008. They have all been approved in a 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

---  ---  F03/0042  IEEE funny values and Standard real generic intrinsic
                     procedures
---  ---  F08/0109  LOCK_TYPE and unlimited polymorphic
---  ---  F08/0145  Can initial-data-target be coindexed?
---  ---  F08/0147  Is generic resolution of elemental assignment done
                     at runtime?
---  ---  F08/0148  Pointer subobject in structure constructor in
                     pure procedure

The text of these interpretations is in N2086.  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, 19 December 2015, in order to be counted.

Thanks,

John.                         
-------------- next part --------------
                                             ISO/IEC JTC1/SC22/WG5 N2086
                                             
      Fortran Interpretations waiting for WG5 ballot, December 4, 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: F03/0042
TITLE:  IEEE funny values and Standard real generic intrinsic
        procedures
KEYWORDS: IEEE-754, real math library
DEFECT TYPE: Interpretation
STATUS: Passed by J3 letter ballot

QUESTION:

Is an infinite result from an infinite argument to a real math
function exceptional (raises an exception)?

Is a NaN result from a NaN argument to a real math function
exceptional (raises an exception)?

What are the results (value and exceptions) for the following
(section 13.7.*) real math library functions [suggested results
for most are included; no exception happens unless specified]:

 ABS(-0.0) returns +0.0
 ABS(+/-infinity) returns +infinity
 ABS(NaN) returns a NaN

 ACOS(x), where |x|>1, returns a NaN and raises invalid
 ACOS(NaN) returns a NaN

 AINT(-0.0) returns -0.0
 AINT(NaN) returns a NaN
 AINT(+infinity) returns +infinity
 AINT(-infinity) returns -infinity

 ANINT(-0.0) returns -0.0
 ANINT(NaN) returns a NaN
 ANINT(+infinity) returns +infinity
 ANINT(-infinity) returns -infinity

 ASIN(x), where |x|>1, returns a NaN and raises invalid
 ASIN(NaN) returns a NaN

 ATAN(-0.0) returns -0.0
 ATAN(+infinity) returns +pi/2
 ATAN(-infinity) returns -pi/2
 ATAN(NaN) returns a NaN
 ATAN2(NaN,x) returns a NaN
 ATAN2(y,NaN) returns a NaN
 ATAN2(+/-0.0, -0.0) returns +/-pi (and not raise invalid)
 ATAN2(+/-0.0, +0.0) returns +/-0.0 (and not raise invalid)
 ATAN2(+/-0.0, x) returns +/-pi for x < 0.0
 ATAN2(+/-0.0, x) returns +/-0.0 for x > 0.0
 ATAN2(y, +/-0.0) returns -pi/2 for y < 0.0
      (and not raise divide by zero)
 ATAN2(y, +/-0.0) returns +pi/2 for y > 0.0
      (and not raise divide by zero)
 ATAN2(+/-y, -infinity) returns +/-pi for finite y > 0.0
 ATAN2(+/-y, +infinity) returns +/-0.0 for finite y < 0.0
 ATAN2(+/-infinity, x) returns +/-pi/2 for finite x
 ATAN2(+/-infinity, -infinity) returns +/-3pi/4
      (and not raise invalid)
 ATAN2(+/-infinity, +infinity) returns +/-pi/4
      (and not raise invalid)

 CEILING(+/-infinity) returns +/-infinity
 CEILING(-0.0) returns -0.0
 CEILING(NaN) returns a NaN

 COS(+/-0.0) returns 1
 COS(NaN) returns a NaN
 COS(+/-infinity) returns a NaN and raises invalid

 COSH(+/-0.0) returns 1
 COSH(NaN) returns a NaN
 COSH(+/-infinity) returns a +infinity DIM(NaN,y) returns a NaN

 DIM(x,NaN) returns a NaN
 DIM(+/-0.0, +/-0.0) returns a +0.0
 DIM(+infinity, -infinity) returns a NaN and raises invalid
 DIM(+infinity, +infinity) returns +0.0
 DIM(-infinity, -infinity) returns +0.0
 DIM(-infinity, +infinity) returns +0.0

 DPROD(NaN,y) returns a NaN
 DPROD(x,NaN) returns a NaN
 DPROD(+/-0.0, +/-infinity) returns a NaN and raises invalid
 DPROD(+/-infinity, +/-0.0) returns a NaN and raises invalid
 DPROD(+/-infinity, +/-infinity) returns an infinity with its sign
 being the XOR of the arguments, and raises no exceptions.
 DPROD(+/-0.0, +/-0.0) returns a zero with its sign
 being the XOR of the arguments, and raises no exceptions.

 EXP(NaN) returns a NaN
 EXP(+/-0.0) returns 1
 EXP(-infinity) returns +0.0
 EXP(+infinity) returns +infinity

 EXPONENT(+/-0.0) returns 0 [should be -HUGE(0)] and raises invalid
 EXPONENT(NaN) returns HUGE(0) and raises invalid
 EXPONENT(+/-INF) returns HUGE(0) and raises invalid
 EXPONENT(denormal) returns the value as if the number were
         normalized and the exponent range were unbounded
 If /e/ is not representable as a default integer, invalid is raised
   and sign(/e/)*HUGE(0) should be returned.

 FLOOR(NaN) returns a NaN
 FLOOR(-0.0) returns -0.0
 FLOOR(+/-infinity) returns +/- infinity

 FRACTION(-0.0) returns -0.0
 FRACTION(NaN) returns a NaN
 FRACTION(denormal) returns the value as if the number were
         normalized and the exponent range were unbounded
 FRACTION(+/-infinity) returns +/- infinity

 INT(NaN) returns an unspecified value and raises invalid
 INT(+/-infinity) returns an unspecified value and raises
    invalid
 INT(+/-large), where large cannot be represented as an integer,
    returns an unspecified value and raises invalid

 LOG(+/-0.0) returns -infinity and raises divide-by-zero
 LOG(NaN) returns a NaN
 LOG(1.0) returns +0.0
 LOG(x), for x < 0, returns a NaN and raises invalid
 LOB(+infinity) returns +infinity

 LOG10(+/-0.0) returns -infinity and raises divide-by-zero
 LOG10(NaN) returns a NaN
 LOG10(1.0) returns +0.0
 LOG10(x), for x < 0, returns a NaN and raises invalid
 LOG10(+infinity) returns +infinity

 MAX(NaN,NaN) returns a NaN
 MAX(NaN,y) returns y [some say it should be NaN]
 MAX(x,NaN) returns x [some say it should be NaN]
 MAX(-0.0,+0.0) returns +0.0
 MAX(-0.0,-0.0) returns -0.0
 MAX(+infinity,y) returns +infinity
 MAX(-infinity,y) returns y

 MIN(NaN,NaN) returns a NaN
 MIN(NaN,y) returns y [some say it should be NaN]
 MIN(x,NaN) returns x [some say it should be NaN]
 MIN(-0.0,+0.0) returns -0.0
 MIN(-0.0,-0.0) returns -0.0
 MIN(-infinity,y) returns -infinity
 MIN(+infinity,y) returns y

 MOD(NaN,y) returns a NaN
 MOD(x,NaN) returns a NaN
 MOD(+/-infinity,y) returns a NaN and raises invalid
 MOD(+/-infinity,+/-infinity) returns a NaN and raises invalid
 MOD(x,+/-0.0) returns a NaN and raises invalid
 MOD(+/-0.0,+/-0.0) returns a NaN and raises invalid

 MODULO(NaN,y) returns a NaN
 MODULO(x,NaN) returns a NaN
 MODULO(+/-infinity,y) returns a NaN and raises invalid
 MODULO(+/-infinity,+/-infinity) returns a NaN and raises invalid
 MODULO(x,+/-0.0) returns a NaN and raises invalid
 MODULO(+/-0.0,+/-0.0) returns a NaN and raises invalid

 NEAREST(NaN,y) returns a NaN
 NEAREST(x,NaN) returns a NaN
 NEAREST(x,+/-0.0) returns a NaN and raises invalid  [why???]
 NEAREST(+infinity,+num) returns +infinity ???
 NEAREST(+infinity,-num) returns +maximum finite number
 NEAREST(-infinity,+num) returns -maximum finite number
 NEAREST(-infinity,-num) returns -infinity ???

 NINT(NaN) returns an unspecified value and raises invalid
 NINT(+/-infinity) returns an unspecified value and raises
     invalid
 NINT(+/-large), where large cannot be represented as an
     integer, returns an unspecified value and raises invalid

 RRSPACING(NaN) returns a NaN
 RRSPACING(+/-infinity) returns +/-infinity
          [differs from current F2003]
 RRSPACING(+/-0.0) returns +0.0
 RRSPACING(+/-denormal) returns ???

 SCALE(NaN,y) returns a NaN
 SCALE(+/-infinity,y) returns +/-infinity
 SCALE(-0.0,y) returns -0.0

 SET_EXPONENT(NaN,y) returns a NaN
 SET_EXPONENT(+/-infinity,y) returns +/-infinity
 SET_EXPONENT(-0.0,y) returns -0.0
 SET_EXPONENT(denormal,y) returns ???

 SIGN(NaN,y), where 0 < y, returns the same NaN,
      but with the sign bit cleared.
 SIGN(NaN,y), where y < 0, returns the same NaN,
      but with the sign bit set.

 SIN(NaN) returns a NaN
 SIN(+/-infinity) returns a NaN and raises invalid
 SIN(-0.0) returns -0.0

 SINH(NaN) returns a NaN
 SINH(+/-infinity) returns +/- infinity
 SINH(-0.0) returns -0.0

 SPACING(NaN) returns a NaN
 SPACING(+/-infinity) returns +infinity
 SPACING(-0.0) returns TINY(+0.0)
 SPACING(denormal) returns TINY(+0.0) ???

 SQRT(NaN) returns a NaN
 SQRT(+infinity) returns +infinity
 SQRT(-0.0) returns -0.0
 SQRT(x), where x < 0.0, returns a NaN and raises invalid

 TAN(NaN) returns a NaN
 TAN(+/-infinity) returns a NaN and raises invalid
 TAN(-0.0) returns -0.0

 TANH(NaN) returns a NaN
 TANH(+/-infinity) returns +/-1.0
 TANH(-0.0) returns -0.0


13.7 [300:13-15] incorrectly requires an infinite result or a
NaN result to always signal some IEEE exception.

Consider changing [300:13] "infinite result" to "infinite result
(from finite arguments)".  Reason: IEEE-754 mathematical
operations on infinity that produce an infinity are
unexceptional.

Consider changing [300:14] "NaN result" to "NaN result (from
non-NaN arguments)".  Reason: IEEE-754 mathematical operations
on quiet NaN operands that produce a quiet NaN result are
unexceptional.

Consider adding to 13.7 [300:15+] something along the lines of:
"Unless specified otherwise, a math function with NaN
argument(s) shall return a NaN, which should be one of the NaN
arguments."  This allows not having to specify the results for
each specific math function.

Consider adding the above suggested cases to each of the 13.7.*
functions, perhaps, with a bold face IEEE sub-heading.

ANSWER:

The erroneous text quoted from 13.7 in Fortran 2003 has been revised
in Fortran 2008, and again by Corrigendum 2 for Fortran 2008, and now
no longer conflicts with the IEEE-754 standard.

To specify the results of all the intrinsics for non-normal values is
beyond the scope of an interpretation.  This could be considered for a
future revision.

EDIT:

None.

SUBMITTED BY: Fred Tydeman

HISTORY: 05-121r1  m171  F03/0042 submitted
         15-248    m208  Revised answer and edits - passed by J3 meeting
         16-103    m209  Passed by J3 letter ballot 16-101

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

NUMBER: F08/0109
TITLE: LOCK_TYPE and unlimited polymorphic
KEYWORD: LOCK_TYPE, unlimited polymorphic
DEFECT TYPE: Erratum
STATUS: Passed by J3 letter ballot

QUESTION:

Assume type LOCK_TYPE from the intrinsic module ISO_Fortran_Env is
available.

Q1. Is allocation of X%C permitted?

  TYPE t
    TYPE(LOCK_TYPE),ALLOCATABLE :: c
  END TYPE
  TYPE(t) :: x[*],y[*]
  ALLOCATE(y%c)
  ALLOCATE(x%c,SOURCE=y%c)

Q2. Is allocation of C permitted?

  class(*), pointer :: C
  type(lock_type), intent(in) :: L[*]

  allocate ( C, source=L )

Q3. Is allocation of C permitted?

  class(*), pointer :: C

  allocate ( LOCK_TYPE :: C )

Q4. Is pointer assignment to C permitted?

  class(*), pointer :: C
  type(lock_type), intent(in), target :: L[*]

  c => L

Q5. Is this ALLOCATE statement conforming?

  CLASS(*),ALLOCATABLE, SAVE :: C[:]
  TYPE(LOCK_TYPE),      SAVE :: X[*]
  ALLOCATE(C,MOLD=X)

ANSWER:

A1. Allocation of X%C is not intended to be allowed.  An edit is
    supplied to correct the requirements on allocation of LOCK_TYPE.

A2. Allocation of C is not intended to be allowed.  An edit is
    supplied to correct the requirements on allocation of LOCK_TYPE.

A3. This allocation of C is permitted.  It cannot violate C1302 because
    that is a syntax constraint.  Only things that are statically
    detectable static properties of the program source text can be
    syntax constraints.  That means that "type" in C1302 can only mean
    "declared type".

    C is CLASS(*) so has no declared type and therefore cannot
    violate C1302.

    Edits are given to fix C1302 to say "declared type" explicitly to
    avoid this confusion.

    Note that it is impossible to actually use the allocated target of
    C in any useful fashion; SELECT TYPE cannot access it because the
    associate-name would be a named lock variable, but it is not a
    coarray so that would not be allowed.

    So this is permitted, but useless, and because it is useless it is
    also harmless.  A future revision could disallow this without the
    concomitant incompatibility inconveniencing any programs.

A4. Pointer assignment to C is permitted.

    As in A3, this is useless but harmless.  A future revision could
    disallow this without the concomitant incompatibility
    inconveniencing any programs.

A5. This statement was intended to be permitted.  An edit is supplied
    to correct the requirements.

Note that the term "potential subobject component" is defined in interp
F08/0124 and will be in Corrigendum 4:

  [6:7+] After definition 1.3.33.2 parent component, insert new term
    "1.3.33.2a
     potential subobject component
     nonpointer component, or potential subobject component of a
     nonpointer component".

EDITS:

[127:8-9] 6.7.1.1 Syntax, C642,
          Change "C_PTR," to "C_PTR or"
          Delete ", LOCK_TYPE ... LOCK_TYPE".

[127:9+] Insert new constraint
  "C643a (R627) If SOURCE= appears, the declared type of <source-expr>
         shall not be LOCK_TYPE or have a potential subobject
         component of type LOCK_TYPE."

[127:18-19] 6.7.1.1, p4,
  Instead of the edit in Corr. 2, make this change to the 10-007r1 text:

    Change "If <allocate-object> is" -> "If an ALLOCATE statement
            has a SOURCE= specifier and an <allocate-object> that is".
    {There is no problem with MOLD=.  "subcomponent" works ok here
     because we have an object not a type.}

  so p4 reads:

    "If an ALLOCATE statement has a SOURCE= specifier and an
     <allocate-object> that is a coarray, <source-expr> shall not have a
     dynamic type of C_PTR, C_FUNPTR, or LOCK_TYPE, or have a
     subcomponent whose dynamic type is LOCK_TYPE."

[399:17] 13.8.2.16 LOCK_TYPE, C1302
     "variable of type LOCK TYPE"
  -> "variable with declared type LOCK_TYPE".

SUBMITTED BY: Van Snyder

HISTORY: 14-164    m204  F08/0109 submitted
         14-164r3  m204  As amended, passed by J3 meeting
         14-258    m205  Failed the J3 letter ballot #31 14-233r1
         15-253    m208  Revised - passed by J3 meeting
         16-103    m209  Passed as amended by J3 letter ballot 16-101

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

NUMBER: F08/0145
TITLE: Can initial-data-target be coindexed?
KEYWORDS: initialization, pointers, coarrays
DEFECT TYPE: Erratum
STATUS: Passed by J3 letter ballot

QUESTION:

In pointer assignment, the standard is quite clear that data-target
cannot be coindexed:

C725 (R737) A data-target shall not be a coindexed object.

And there are a couple of notes related to this:

NOTE 7.45
A data pointer and its target are always on the same image. A coarray
may be of a derived type with pointer or allocatable subcomponents. For
example, if PTR is a pointer component, Z[P]%PTR is a reference to the
target of component PTR of Z on image P. This target is on image P and
its association with Z[P]%PTR must have been established by the
execution of an ALLOCATE statement or a pointer assignment on image P.

NOTE 7.46
A pointer assignment statement is not permitted to involve a coindexed
pointer or target, see C723 and C725. This prevents a pointer
assignment statement from associating a pointer with a target on
another image. If such an association would otherwise be implied, the
association status of the pointer becomes undefined. For example, a
derived-type intrinsic assignment where the variable and expr are on
different images and the variable has an ultimate pointer component.

Fortran 2008 added the ability to specify an initial-data-target in
pointer initialization:

R505 initialization is = constant-expr
                    or => null-init
                    or => initial-data-target
R506 null-init      is function-reference

C510 (R503) If => appears in initialization, the entity shall have the
POINTER attribute. If = appears in initialization, the entity shall not
have the POINTER attribute.

C511 (R503) If initial-data-target appears, object-name shall be
data-pointer-initialization compatible with it (4.5.4.6).

Initial-data-target is defined in 4.5.4.6 and the only relevant
constraint for it is:

C461 (R443) The designator shall designate a nonallocatable variable
that has the TARGET and SAVE attributes and does not have a vector
subscript. Every subscript, section subscript, substring starting
point, and substring ending point in designator shall be a constant
expression.

The definition of "data-pointer-initialization compatible" is:

"A pointer variable or component is data-pointer-initialization
compatible with a target if the pointer is type compatible with the
target, they have the same rank, all nondeferred type parameters of the
pointer have the same values as the corresponding type parameters of
the target, and the target is contiguous if the pointer has the
CONTIGUOUS attribute."

Given this, is initializing a pointer to a coindexed object permitted?

For example:

program test
integer, save, target :: C[*]
integer, pointer :: P => C[3] ! Permitted?
end

While ordinary pointer assignment to a coindexed object is prohibited
by C725, there is no corresponding constraint prohibiting such
association by way of data pointer initialization.

Note that 16.5.2.5p1(2) says that pointer-assigning to a target on a
different image causes the pointer to become undefined. Since the
initialization occurs on all images, and it's not possible to restrict
the target to only the same image, the effect would be to make a
program that does this nonconforming.

ANSWER:

No, this was not intended to be permitted. A clarifying edit is
provided.

EDITS to 10-007r1:

[70:3] 4.5.4.6

In the first sentence of C461, insert ", noncoindexed" after
"nonallocatable" so that the sentence reads:

C461 (R443) The designator shall designate a nonallocatable,
noncoindexed variable that has the TARGET and SAVE attributes and
does not have a vector subscript.

SUBMITTED BY: Steve Lionel

HISTORY: 15-216    m208  F08/0145 submitted - passed by J3 meeting
         16-103    m209  Passed by J3 letter ballot 16-101

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

NUMBER: F08/0147
TITLE: Is generic resolution of elemental assignment done at runtime?
KEYWORDS: Type-bound defined assignment, Allocatable
DEFECT TYPE: Erratum
STATUS: Passed by J3 letter ballot

QUESTION:

Consider

  Module da_module
    Type t
      Real c
    End Type
    Interface Assignment(=)
      Module Procedure edasgn
    End Interface
  Contains
    Elemental Subroutine edasgn(a,b)
      Class(t),Intent(Out) :: a
      Class(t),Intent(In) :: b
      a%c = -b%c
    End Subroutine
  End Module
  Program edatest
    Call test(10,10,13)
  Contains
    Subroutine test(n,n2,m)
      Use da_module
      Type(t) :: x(n),z(m)
      Type(t),Allocatable :: y(:)
      x%c = [ (i,i=1,n) ]
      z%c = [ (i,i=1,m) ]
      Allocate(y(n2),Source=t(0))
      y = x                        ! A
      Print 1,y
    1 Format(*(1X,F0.1,:))
      y = z                        ! B
      Print 1,y
    End Subroutine
  End Program

According to 7.2.1.2 Intrinsic assignment statement, an assignment
statement is an intrinsic assignment statement if (and only if) it
is not a defined assignment statement.  According to 7.2.1.4 Defined
assignment statement, a defined assignment statement needs to have a
subroutine that defines the assignment "x1 = x2".  For elemental
subroutines (item (5)(b)), that is true only if
  "x1 and x2 are conformable"
which when x1 and x2 are both arrays, means "has the same shape".
For the example above, in the assignment marked (A), x and y will be
conformable (as both n and n2 are equal to 10), making that a defined
assignment, thus the PRINT statement after it would print
 -1.0 -2.0 -3.0 -4.0 -5.0 -6.0 -7.0 -8.0 -9.0 -10.0
while in the assignment statement marked (B), y and z will not be
conformable (n2 being 10 and m being 13), making it an intrinsic
assignment.  In this case, because Y is allocatable it will be
reallocated, and so the output from the second PRINT statement would
be
 1.0 2.0 3.0 4.0 5.0 6.0 7.0 8.0 9.0 10.0 11.0 12.0 13.0

However, this would seem to violate the fundamental principle that
generic references are resolvable at compile time.  It would also
seem to be nearly useless since if the variable is not allocatable
the shapes are required to conform anyway.

Is this feature intended to work like this?

ANSWER:

No, this was a mistake.  Edits are provided to remove the runtime
generic resolution.

After the edits:
  1) The assignment A is defined assignment and is conforming (from 
     first edit).

  2) The assignment B is defined assignment but is not standard conforming,
     since the shapes differ (from second edit).
 
  3) For a defined assignment statement, auto-reallocation of 
     allocatables does not occur, as that is only done by an intrinsic 
     assignment statement.

EDITS:

[24:11+] 1.6.2 Fortran 2003 compatibility, insert new incompatibility
  "Fortran 2003 interpreted assignment to an allocatable variable
   from a nonconformable array as intrinsic assignment, even when an
   elemental defined assignment was in scope; this part of ISO/IEC
   1539 does not permit assignment from a nonconformable array in
   this context.".
{The unintended extension is weird and violates our own principles,
 but is not in itself contradictory or ambiguous so this is an
 incompatibility.}

[157:14] 7.2.1.4 Defined assignment statement, p2, item (5)(b),
         Change "$x_1$ and $x_2$ are conformable"
         to "$x_2$ is scalar or has the same rank as $x_1$".
{$x_1$ is TeX for italics x subscript 1.}

[157:16] Same subclause, p3, append new sentence
  "If the subroutine is elemental, $x_2$ shall have the same shape as
   $x_1$."
{Retain conformability as a normal requirement instead of as a
 condition.}

SUBMITTED BY: Malcolm Cohen

HISTORY: 15-219    m208  F08/0147 submitted - passed by J3 meeting
         16-103    m209  Passed as amended by J3 letter ballot 16-101

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

NUMBER: F08/0148
TITLE: Pointer subobject in structure constructor in pure procedure
KEYWORDS: pointer subobject, structure constructor, pure procedure
DEFECT TYPE: Erratum
STATUS: Passed by J3 letter ballot

QUESTION:

Consider the module

program P

  type :: T1
    integer, pointer :: P1
  end type T1

  type :: T2
    type(t1) :: P2
  end type T2

  type(t1), target :: V1

  allocate ( V1%p1, source = 42 )

contains

  pure subroutine S ( )
    type(t2) :: A
  1 a = t2(v1)
    a%p2%p1 = a%p2%p1 + 1
  end subroutine S

end program P

Item (3) in the list in constraint C1283 in subclause 12.7 prohibits
an object that is accessed by host or use association (and other
categories) to be the <expr> in a structure constructor that
corresponds to a component that has the POINTER attribute.  It is
silent concerning type constructors for types that have potential
subobject components with the POINTER attribute.

Is the statement labeled 1 permitted?  If so, was that intended?

ANSWER:

The statement labeled 1 was inadvertently allowed because V1
corresponds to a component of the structure constructor for type T2
that does not have the POINTER attribute.

An edit is provided to correct this mistake.

EDIT:

[312:35 12.7p2 C1283(3)] Replace this list item by
  "(3) as the <expr> corresponding to a component in a
       <structure-constructor> if the component has the POINTER
       attribute or has a pointer component at any level of
       component selection,"

SUBMITTED BY: Van Snyder

HISTORY: 15-249    m208  F08/0148 submitted
         15-249r1  m208  fix typos - passed J3 meeting
         16-103    m209  Passed as amended by J3 letter ballot 16-101

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



More information about the J3 mailing list