[Bug fortran/93690] New: Type Bound Generic Assignment Bug Using Intrinsic Assignments

2020-02-11 Thread floschiffmann at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=93690

Bug ID: 93690
   Summary: Type Bound Generic Assignment Bug Using Intrinsic
Assignments
   Product: gcc
   Version: 9.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: floschiffmann at gmail dot com
  Target Milestone: ---

Good morning,

I ran across a problem when using a Type bound assignment (TBA). I have two
type, the type with TBA type(Inner), and type (Outer) which has inner as a
member. If now Type(outer) is assigned to another type(outer), the Inner
assignment is only called if it is done elementwise. The vector assignment does
not call the type(Inner) assignment. As I understand the standard, the vector
assignment should call the TBA element by element.

As a side note, the assignment is called if assignMe is made ELEMENTAL IMPURE.
While nice as a work around, I can't see an obvious reason why this would be
the correct behavior.

Here is the test code, which shows this behavior 

! Example start =
MODULE Classes
IMPLICIT NONE

TYPE Inner
   CONTAINS
   PROCEDURE :: assignMe
   GENERIC   :: assignment(=) => assignMe 
END TYPE

TYPE Outer
   TYPE(Inner):: mInner
END TYPE
CONTAINS

   SUBROUTINE assignMe(self, input)
  CLASS(Inner), INTENT(OUT)  ::  self
  CLASS(Inner), INTENT(IN)  ::  input

  WRITE(*,*)"ASSIGNMENT CALLED"   
   END SUBROUTINE

END MODULE

PROGRAM test
   USE Classes
   IMPLICIT NONE
   TYPE(Outer)  :: mOuter(1), reassigned(1)

WRITE(*,*)"Intrinsic assignment works when called element wise"
   reassigned(1)=mOuter(1)
WRITE(*,*)"Does not work when called as vector assignment"
   reassigned=mOuter

END PROGRAM
! Example end =

best regards

Flo

[Bug fortran/93691] New: Type bound assignment causes too many finalization of derived type when part of other type

2020-02-11 Thread floschiffmann at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=93691

Bug ID: 93691
   Summary: Type bound assignment causes too many finalization of
derived type when part of other type
   Product: gcc
   Version: 9.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: floschiffmann at gmail dot com
  Target Milestone: ---

Good morning,

when writing a reference counting scheme, I cam across this slightly intricate
bug. I suspect this is related to a problem in the type bound assignment but I
could not pin it down.

The problem:
Type(Inner) has type bound assignment and Final.
   -assignment associates output reference counter to input reference counter
and incrments
   -final decrements reference counter and deallocates reference count pointer
when 0

Type(outer) has type(inner) as member.

If Type(inner) is used by itself everything works correctly
However, if assignment of type(outer) to type(outer) is made, an additional
finalization is invoked (the third with an unassociated reference counter).

Here is the simplest test code I could produce:

! ==  BEGIN TEST CODE 

MODULE Classes
IMPLICIT NONE

TYPE   :: Inner
   INTEGER, POINTER  :: icount
   CONTAINS
   PROCEDURE :: init
   PROCEDURE :: assignMe
   GENERIC   :: assignment(=) => assignMe
   FINAL :: deleteIt
END TYPE

   TYPE Outer
  TYPE(Inner):: ext
   END TYPE
CONTAINS
   SUBROUTINE init(self)
  CLASS(Inner), INTENT(INOUT)  ::  self

  ALLOCATE(self%icount)
  self%icount=1
   END SUBROUTINE 

! Destrutor, if data is assigned decrement counter and delete once we reach 0
   SUBROUTINE deleteIt(self)
  TYPE(Inner)  ::  self

WRITE(*,*)"FINAL CALLED with icount =", self%icount, "LOC =",LOC(self%icount)
 self%icount=self%icount-1
 IF(self%icount<=0)THEN ! usually == 0 but <=0 better shows the problem
self%icount=-100
WRITE(*,*)"  DEALLOCATING ICOUNT at LOC=", LOC(self%icount)
DEALLOCATE(self%icount)
 END IF
   END SUBROUTINE

! The basic assigment routine, set pointer to input data pointer and increment
counter 
   SUBROUTINE assignMe(self, input)
  CLASS(Inner), INTENT(INOUT)  ::  self
  CLASS(Inner), INTENT(IN)  ::  input
 self%icount => input%icount
 self%icount=self%icount+1
   END SUBROUTINE


END MODULE

PROGRAM test

   USE Classes

IMPLICIT NONE

WRITE(*,*)"Direct Call on inner performs only 2 FINALIZATIONS"
   BLOCK
  TYPE(Inner)  :: inner1, inner2
  CALL inner1%init()
  inner2=inner1
   END BLOCK
WRITE(*,*)
WRITE(*,*)"Indirect Call, 3 FINALIZATIONS, last with dangling pointer on
TYPE(inner)%icount"
   BLOCK
  TYPE(Outer)  :: Outer1, Outer2
  CALL Outer1%ext%init()
  Outer2=Outer1
   END BLOCK 
END 

!= END TEST CODE 


 Note: in Final comparison is for <= 0 to cause double free

best regards
Flo

[Bug fortran/93690] Type Bound Generic Assignment Bug Using Intrinsic Assignments

2020-02-11 Thread floschiffmann at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=93690

--- Comment #2 from Florian Schiffmann  ---
Hi Steve,

the complication here is that it is not the type with the assignment that is a
vector but the Outer type. The type with assignment is a scalar member of the
vector type. Hence the first question should be how the intrinsic assignment of
the vector of Type(outer) is handled.

Thanks to FortranFan on the comp.lang.fortran group:

cite 
[Note 18-007r1 document toward Fortran 2018 states in Section 10.2.1.3
Interpretation of intrinsic assignments, page 161, paragraph 6:

"If the variable is an array, the assignment is performed element-by-element on
corresponding array elements of the variable and expr"

and on page 163, paragraph 13:

"An intrinsic assignment where the variable is of derived type is performed as
if each component of the variable were assigned from the corresponding
component of expr using .. defined assignment for each nonpointer 
nonallocatable component of a type that has a type-bound defined assignment
consistent with the component, intrinsic assignment for each other nonpointer
nonallocatable component .." ]

According to me, this means that the intrinsic assignment working on outer
should work element wise. Then for each element the scalar assignment should be
called (not the vector version).

I can't say I am sure about it either as reading the standard gives me a
headache :). However, to me it makes sense as 

with my interpretation:
You have to inspect the Types containing the one with TBA
vs your interpretation:
You have to inspect the Types containing the one with TBA plus all direct and
indirect uses of the types (if vectors or not)

to decide whether the assignment has to be an elemental subroutine. 
Not sure whether I made perfect sense there but I hope you can decipher my
idea.

Flo

[Bug fortran/93690] Type Bound Generic Assignment Bug Using Intrinsic Assignments

2020-02-11 Thread floschiffmann at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=93690

Florian Schiffmann  changed:

   What|Removed |Added

 CC||floschiffmann at gmail dot com

--- Comment #3 from Florian Schiffmann  ---
Hi Steve,

the complication here is that it is not the type with the assignment that is a
vector but the Outer type. The type with assignment is a scalar member of the
vector type. Hence the first question should be how the intrinsic assignment of
the vector of Type(outer) is handled.

Thanks to FortranFan on the comp.lang.fortran group:

cite 
[Note 18-007r1 document toward Fortran 2018 states in Section 10.2.1.3
Interpretation of intrinsic assignments, page 161, paragraph 6:

"If the variable is an array, the assignment is performed element-by-element on
corresponding array elements of the variable and expr"

and on page 163, paragraph 13:

"An intrinsic assignment where the variable is of derived type is performed as
if each component of the variable were assigned from the corresponding
component of expr using .. defined assignment for each nonpointer 
nonallocatable component of a type that has a type-bound defined assignment
consistent with the component, intrinsic assignment for each other nonpointer
nonallocatable component .." ]

According to me, this means that the intrinsic assignment working on outer
should work element wise. Then for each element the scalar assignment should be
called (not the vector version).

I can't say I am sure about it either as reading the standard gives me a
headache :). However, to me it makes sense as 

with my interpretation:
You have to inspect the Types containing the one with TBA
vs your interpretation:
You have to inspect the Types containing the one with TBA plus all direct and
indirect uses of the types (if vectors or not)

to decide whether the assignment has to be an elemental subroutine. 
Not sure whether I made perfect sense there but I hope you can decipher my
idea.

Flo