[Bug fortran/97380] New: polymorphic array assignment for `PACK`: ICE and runtime segfaults
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=97380 Bug ID: 97380 Summary: polymorphic array assignment for `PACK`: ICE and runtime segfaults Product: gcc Version: 10.2.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Created attachment 49351 --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=49351&action=edit program that reproduces the issue I have ICE and runtime segfaults when performing polymorphic *array* assignments with gfortran 7.4.0, 9.2.0 and 10.2.0. - assignment using a DO loop --> everything OK - assignment using an array, like: array(1:5) = array([2,4,6,8,10]) --> ICE segfault - assignment using PACK intrinsic, like: array(1:5) = pack(array,mod([(j,j=1,10)],2)==0) --> RUNTIME segfault This is a sample program that reproduces these issues: module m implicit none type, public :: t integer :: i = 0 contains procedure, private, pass(this) :: t_assign => t_to_t generic :: assignment(=) => t_assign end type t type, public, extends(t) :: tt integer :: j = 0 contains procedure, private, pass(this) :: t_assign => t_to_tt end type tt contains elemental subroutine t_to_t(this,that) class(t), intent(inout) :: this class(t), intent(in ) :: that this%i = that%i end subroutine t_to_t elemental subroutine t_to_tt(this,that) class(tt), intent(inout) :: this class(t ), intent(in ) :: that this%i = that%i select type (thatPtr=>that) type is (t) this%j = 0 type is (tt) this%j = thatPtr%j class default ! Cannot stop here this%i = -1 this%j = -1 end select end subroutine t_to_tt end module m program test_poly_pack use m implicit none integer, parameter :: n = 100 integer :: i,j class(t), allocatable :: poly(:),otherPoly(:) allocate(t :: poly(n)) allocate(t :: otherPoly(10)) ! Assign dummy values forall(i=1:n) poly(i)%i = i ! Array assignment with indices => ICE segfault: ! internal compiler error: Segmentation fault otherPoly(1:10) = poly([10,20,30,40,50,60,70,80,90,100]) ! Scalar assignment with loop -> OK do i=1,10 otherPoly(i) = poly(10*i) end do ! Array assignment with PACK => Compiles OK, Segfault on runtime. GDB returns: ! Thread 1 received signal SIGSEGV, Segmentation fault. ! 0x0040163d in m::t_to_t (this=..., that=...) at test_poly_pack.f90:31 ! 31this%i = that%i otherPoly(1:10) = pack(poly,mod([(j,j=1,100)],10)==0) do i=1,10 print *, ' polymorphic(',i,')%i = ',otherPoly(i)%i end do end program test_poly_pack Thanks, Federico
[Bug fortran/97380] polymorphic array assignment for `PACK`: ICE and runtime segfaults
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=97380 --- Comment #2 from federico --- I have an update: if I remove the ELEMENTAL property from the assignment routines, I get this error in both the PACK and the array assignments: Error: Nonallocatable variable must not be polymorphic in intrinsic assignment at (1) - check that there is a matching specific subroutine for '=' operator I guess that means that I don't have an assignment interface that works with array input, Federico
[Bug fortran/97455] New: ICE on invalid code (wrong pointer assignment) in SELECT TYPE construct
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=97455 Bug ID: 97455 Summary: ICE on invalid code (wrong pointer assignment) in SELECT TYPE construct Product: gcc Version: 9.2.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Created attachment 49383 --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=49383&action=edit Test program Hi, the following code produces an ICE Segmentation fault with gfortran 9.2.0: module m implicit none type, public :: t end type t type, public, extends(t) :: tt end type tt type, public :: container class(t), allocatable :: x(:) end type container contains subroutine polymorphic(self) type(container), intent(in) :: self ! select type (x => self%x(:)) ! Correct code select type (x => x(:)) ! This wrong code produces an ICE type is (t) print *, 'type(t)' type is (tt) print *, 'type(tt)' class default print *, 'other' end select end subroutine polymorphic end module m program test_ice use m implicit none type(container) :: c call polymorphic(c) end program test_ice Some similar bug (#86551) was already reported, but this deals with the pointer associating to itself so I thought to open a new one instead.
[Bug fortran/97380] polymorphic array assignment for `PACK`: ICE and runtime segfaults
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=97380 --- Comment #3 from federico --- Created attachment 49392 --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=49392&action=edit Other test program highlights issue in accessing polymorphic arrays with arrays
[Bug fortran/97380] polymorphic array assignment for `PACK`: ICE and runtime segfaults
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=97380 --- Comment #4 from federico --- I've attached another program that perhaps highlights the problem better. Even just *accessing* a polymorphic array with an array causes wrong output with gfortran 9.2.0: The attached program sends elements [3,6,9] in a polymorphic array to a subroutine, which should then print some info: their ID in the original array. Instead of printing 3,6,9, it prints 3,4,5 when the input array was polymorphic: module m implicit none type, public :: t integer :: i = 1 end type t type, public, extends(t) :: tt integer :: j end type tt contains subroutine print_array(x,msg) class(t), intent(in) :: x(:) character(*), intent(in) :: msg integer :: j print *, msg//' :: size(x)=',size(x) select type (xx=>x(:)) type is (t) do j=1,size(xx) print *, 'x(',j,')%i = ',xx(j)%i end do type is (tt) do j=1,size(xx) print *, 'x(',j,')%i = ',xx(j)%i,' %j=',xx(j)%j end do end select end subroutine print_array end module m program test_poly_access_array use m implicit none class(t), allocatable :: poly_t(:),poly_tt(:) type (t), allocatable :: nonpoly_t (:) type(tt), allocatable :: nonpoly_tt(:) integer :: i integer, dimension(3) :: chunk = [3,6,9] allocate(t :: poly_t( 10)) allocate(tt :: poly_tt(10)) allocate( nonpoly_t(10),nonpoly_tt(10)) do i=1,10 poly_t(i)%i = i poly_tt(i)%i = i select type (ptt=>poly_tt(:)) type is (tt) ptt(i)%j = i end select nonpoly_t(i)%i = i nonpoly_tt(i)%i = i nonpoly_tt(i)%j = i end do call print_array(nonpoly_t(chunk),'nonpoly_t') call print_array(nonpoly_tt(chunk),'nonpoly_tt') call print_array(poly_t(chunk),'poly_t') call print_array(poly_tt(chunk),'poly_tt') end program test_poly_access_array Output is: nonpoly_t :: size(x)= 3 ! Non-polymorphic, base type: OK x( 1 )%i =3 x( 2 )%i =6 x( 3 )%i =9 nonpoly_tt :: size(x)= 3 ! Non-polymorphic, extended type: OK x( 1 )%i =3 %j= 3 x( 2 )%i =6 %j= 6 x( 3 )%i =9 %j= 9 poly_t :: size(x)= 3 ! Polymorphic, base type: WRONG x( 1 )%i =3 x( 2 )%i =4 x( 3 )%i =5 poly_tt :: size(x)= 3! Polymorphic, extended type: WRONG x( 1 )%i =3 %j= 3 x( 2 )%i =4 %j= 4 x( 3 )%i =5 %j= 5
[Bug fortran/98558] New: Scalar character parameter does not print warning if actual length >1
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98558 Bug ID: 98558 Summary: Scalar character parameter does not print warning if actual length >1 Product: gcc Version: 9.2.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Created attachment 49898 --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=49898&action=edit test program More of a suggestion than a bug (I don't see memory issues). If I initialize a CHARACTER, PARAMETER variable with a string whose lenght is >1, no warnings are printed in gcc/gfortran 9.2.0: program test_char_parameter implicit none character , parameter :: a = 'a' ! OK character , parameter :: b = 'b' ! NO -> No warnings printed! character(len=1), parameter :: c = 'c' ! NO -> No warnings printed! character(len=*), parameter :: d = 'd' ! OK print *, a print *, b print *, c print *, d end program test_char_parameter Best, Federico
[Bug fortran/98558] Scalar character parameter does not print warning if actual length >1
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98558 federico changed: What|Removed |Added Resolution|--- |INVALID Status|WAITING |RESOLVED --- Comment #2 from federico --- My bad, I haven't tested this with the warning flags on. Thanks! Federico
[Bug fortran/59202] Erroneous argument aliasing with defined assignment
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=59202 federico changed: What|Removed |Added CC||federico.perini at gmail dot com --- Comment #3 from federico --- Created attachment 50918 --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=50918&action=edit test program for self-assignment with derived type
[Bug fortran/59202] Erroneous argument aliasing with defined assignment
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=59202 --- Comment #4 from federico --- The self-assignment issue is present even if the derived type has no allocatable components. Here is a sample test program that gives an error with gfortran 10.2.0: module assign implicit none private type, public :: t integer :: a contains procedure :: destroy=>t_destroy procedure :: assign=>t_assign generic :: assignment(=) =>assign end type t contains elemental subroutine t_destroy(this) class(t), intent(inout) :: this this%a = 0 end subroutine t_destroy subroutine t_assign(this,that) class(t), intent(inout) :: this class(t), intent(in) :: that call this%destroy() ! Clean memory first select type (thatPtr=>that) type is (t) this%a = thatPtr%a end select end subroutine t_assign end module assign program test use assign type(t), allocatable :: t1(:) allocate(t1(10)) do i=1,10 t1(i)%a = i end do n = 0 do i=1,10 if (mod(i,2)/=0) then n = n + 1 t1(n) = t1(i) print *, 'i=',i,' t(i)%a=',t1(i)%a,' expected t(i)%a=',i,': ',merge('ERROR!','OK',t1(i)%a/=i) endif end do end program test
[Bug fortran/108431] New: Loop variable reaching integer `huge` causes infinte loop
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108431 Bug ID: 108431 Summary: Loop variable reaching integer `huge` causes infinte loop Product: gcc Version: 12.2.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Consider the following tiny program: program test_huge use iso_fortran_env, only: int8 integer(int8) :: i do i=-huge(i),huge(i) print "('i=',i10,' b=',b8.8)", i,i end do end With gfortran 12.2 on Mac, this causes an infinite loop that never ends. I guess there is a problem with huge(i)=127, because if use the same bounds with an implicit loop, I get: 3 | integer(int8), parameter :: a(*) = [(i,i=-huge(i),huge(i))] | 1 Warning: DO loop at (1) is undefined as it overflows [-Wundefined-do-loop] I've put this example on godbolt at https://godbolt.org/z/6x7K9a6a3 . Apparently, this issue affects all gfortran versions from 7.1 up (6.3 is the last working version), Federico
[Bug fortran/108431] Loop variable reaching integer `huge` causes infinte loop
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108431 federico changed: What|Removed |Added Resolution|--- |INVALID Status|UNCONFIRMED |RESOLVED --- Comment #1 from federico --- I've just found from previous discussions on Fortran forums that this may not be a bug in the compiler but rather a gray area in the Fortran standard. So I will close the bug as "invalid".
[Bug fortran/109076] New: class extending abstract type with deferred procedures, with another unrelated procedure interface, crashes on valid code
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109076 Bug ID: 109076 Summary: class extending abstract type with deferred procedures, with another unrelated procedure interface, crashes on valid code Product: gcc Version: 12.2.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Hello gfortran/gcc team, I've reduced my issue to the following minimum viable example. Please note I haven't shortened the names because changing them sometimes solves this issue. - The abstract class has deferred procedures, with their abstract interface - The extended type implements them, AND it has another unrelated subroutine that contains a procedure interface - A casual solution is found by either shortening the unrelated subroutine name, or removing some imports from the abstract interface ==> With all gfortran versions from 12.2.0 down to 4.9, I get an "interface mismatch" issue: /app/example.f90:13:15: 13 | procedure :: expand => i_expand | 1 Error: Argument mismatch for the overriding procedure 'expand' at (1): Shape mismatch in argument 'array' The code can be found to play with here: https://godbolt.org/z/GfKGE1cYa And is also here: module my_mod use iso_fortran_env, only: real64 implicit none private type, abstract, public :: parallel_class contains procedure(par_expand_r64), pass(this), deferred :: expand end type parallel_class type, public, extends(parallel_class) :: interpolator contains procedure :: expand => i_expand end type interpolator abstract interface pure subroutine par_expand_r64(this,array) import parallel_class,real64 class(parallel_class), intent(inout) :: this real(real64), intent(in) :: array(:) end subroutine par_expand_r64 pure function interp_fun(ndim,x) result(fun_values) ! ** SOLUTION #1 *** !import real64 ! works with this import real64,interpolator ! this crashes gfortran-12 integer , intent(in) :: ndim real(real64), intent(in) :: x real(real64), dimension(ndim) :: fun_values end function interp_fun end interface contains !** SOLUTION #2 ** !subroutine create_object(this,fun) ! works with this name subroutine interpolator_create_fromfun_fixedstep(this,fun) ! crashes with this name class(interpolator) , intent(inout) :: this procedure(interp_fun) :: fun print *, 'hello world' end subroutine ! Get comm size pure subroutine i_expand(this,array) class(interpolator), intent(inout) :: this real(real64), intent(in) :: array(:) end subroutine i_expand end module my_mod Thank you, Federico
[Bug fortran/109076] class extending abstract type with deferred procedures, with another unrelated procedure interface, crashes on valid code
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109076 --- Comment #2 from federico --- Sorry I meant it does not compile what I think is valid code: subroutine i_expand matches the given abstract interface exactly, I can't find a shape mismatch. I wound two ways that will make the error go away: - remove `interpolator` from the import statement in the abstract interface (was not being used) - change the name of the subroutine to a shorter one, in a non-deterministic way
[Bug fortran/104927] New: Invalid array size specification accepted
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=104927 Bug ID: 104927 Summary: Invalid array size specification accepted Product: gcc Version: 10.3.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Created attachment 52627 --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=52627&action=edit test program A low priority bug, I guess. The following invalid code with double array size specifications is accepted by gfortran 10.3.0 all the way down to at least 8.1.0: integer, allocatable, dimension(:,:) :: a(:) integer, allocatable, dimension(:) :: b(:,:) integer, allocatable, dimension(:,:) :: c(:,:) It appears that the shape then picked by gfortran is that on the right hand side, but no errors/warning are printed. I've attached a test program for this. Thanks for the hardwork on gfortran! Federico
[Bug fortran/104927] Invalid array size specification accepted
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=104927 federico changed: What|Removed |Added Status|UNCONFIRMED |RESOLVED Resolution|--- |INVALID --- Comment #2 from federico --- Yeah I'm surprised but wrong. The "overriding" option of the rhs size specification is pretty clear from that statement from the standard. This makes it even more evident: program test_invalid_shape implicit none integer, dimension(2,2) :: a(3),b(2,5),c print *, 'shape(a) = ',shape(a) print *, 'shape(b) = ',shape(b) print *, 'shape(c) = ',shape(c) end program test_invalid_shape produces shape(a) =3 shape(b) =2 5 shape(c) =2 2
[Bug fortran/106731] New: ICE on automatic array of derived type with DTIO
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106731 Bug ID: 106731 Summary: ICE on automatic array of derived type with DTIO Product: gcc Version: 12.1.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- A derived type that has user-defined I/O causes ICE on all gfortran versions 7 to 12.1.0, whenever it's being used as an automatic object. The error is at 63 | type(t) :: automatic(n) | 1 internal compiler error: in gfc_trans_auto_array_allocation, at fortran/trans-array.cc:6617 This does not happen if the derived type is allocated. Here's the simplest example: module causes_ice implicit none type :: t real(8) :: x contains procedure, private :: write_formatted generic :: write(formatted) => write_formatted end type t contains subroutine write_formatted(this, unit, iotype, v_list, iostat, iomsg) class(t), intent(in) :: this integer, intent(in) :: unit character(*), intent(in) :: iotype integer, intent(in) :: v_list(:) integer, intent(out) :: iostat character(*), intent(inout) :: iomsg write(unit, '(a)', iostat=iostat, iomsg=iomsg) 'dummy' end subroutine write_formatted end module causes_ice module use_t use causes_ice implicit none public :: automatic_alloc contains subroutine automatic_alloc(n) integer, intent(in) :: n ! Automatic array: ICE! type(t) :: automatic(n) ! Allocatable: works type(t), allocatable :: alloc(:) allocate(alloc(n)) ! Do anything print *, 'n=',n,automatic(n)%x end subroutine automatic_alloc end module use_t program test use use_t call automatic_alloc(1) end program test I could find other DTIO-related bugs, but none seemed related with the allocation type.
[Bug fortran/106731] ICE on automatic array of derived type with DTIO
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106731 --- Comment #2 from federico --- For the sake of completeness, fixed-size does not cause an ICE: type(t) :: fixed(5) ! works
[Bug fortran/106731] ICE on automatic array of derived type with DTIO
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106731 --- Comment #4 from federico --- The TREE_STATIC assert should be valid according to what reported in the implementation at report https://gcc.gnu.org/bugzilla/show_bug.cgi?id=48298 But, I can't tell what that means.
[Bug fortran/106731] ICE on automatic array of derived type with DTIO
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106731 --- Comment #6 from federico --- Yeah this popped up playing with DTIO, this feature is not widely used apparently. I'll also try to get a copy of the gcc source code and build pipeline to see if I can help.
[Bug fortran/106750] New: Memory leak calling section of derived type containing `allocatable` entries
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106750 Bug ID: 106750 Summary: Memory leak calling section of derived type containing `allocatable` entries Product: gcc Version: 9.2.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Running a large CFD program I've found a memory leak gfortran 9.2.0 (sorry: unable to test other versions on that system) that occurs when: - derived type contains `allocatable` entries - a chunk of an array of the aforementioned derived type is used as input to a function - happens whether or not the derived type contains a final routine Here's a minimal working example: module tmod implicit none type, public :: t integer :: i,j,k integer, allocatable :: a(:) ! No leaks if these are fixed-size integer, allocatable :: b(:) ! No leaks if these are fixed-size !integer :: a(3),b(20) ! uncomment to test fixed-size end type t contains integer function do_with_array(ts) result(l) type(t), intent(in) :: ts(2) integer :: i(2),j(2),k(2) i = max(ts(:)%i,0) j = max(ts(:)%j,0) k = max(ts(:)%k,0) l = sum(i+j+k) end function integer function do_with_scalars(t1,t2) result(l) type(t), intent(in) :: t1,t2 integer :: i(2),j(2),k(2) i(1) = max(t1%i,0); i(2) = max(t2%i,0) j(1) = max(t1%j,0); j(2) = max(t2%j,0) k(1) = max(t1%k,0); k(2) = max(t2%k,0) l = sum(i+j+k) end function end module tmod program test use tmod implicit none integer, parameter :: n = 1000 type(t), allocatable :: ts(:) integer :: j(n),choose(2),i,k(n) real :: x(2) ! Initialize with anything allocate(ts(n)); do i=1,n ts(i) = t(i,2*i,3*i,[(i,i=1,3)],[(2*i,i=1,20)]) end do ! Do several calls do i=1,n call random_number(x); choose = ceiling(x*n) ! [leak #1] j(i) = do_with_array(ts(choose)) ! [#1] MEMORY LEAK ! no leak ever k(i) = do_with_scalars(ts(choose(1)),ts(choose(2))) end do print *, 'sum=',sum(j) ! [leak #2] happens if ts is not deallocated. Shouldn't a program work like a ! subroutine, and deallocate everything that's going out of scope? deallocate(ts) end program test The results with valgrind are: [perini1@srv0 ~]$ valgrind --tool=memcheck --leak-check=yes --track-origins=yes ./a.out ==49159== Memcheck, a memory error detector ==49159== Copyright (C) 2002-2012, and GNU GPL'd, by Julian Seward et al. ==49159== Using Valgrind-3.8.1 and LibVEX; rerun with -h for copyright info ==49159== Command: ./a.out ==49159== sum= 5960916 ==49159== ==49159== HEAP SUMMARY: ==49159== in use at exit: 197,026 bytes in 4,001 blocks ==49159== total heap usage: 6,023 allocs, 2,022 frees, 446,610 bytes allocated ==49159== ==49159== 24,000 bytes in 2,000 blocks are definitely lost in loss record 2 of 3 ==49159==at 0x4C28A2E: malloc (vg_replace_malloc.c:270) ==49159==by 0x402204: MAIN__ (test_leak.f90:55) ==49159==by 0x4026C9: main (test_leak.f90:36) ==49159== ==49159== 160,000 bytes in 2,000 blocks are definitely lost in loss record 3 of 3 ==49159==at 0x4C28A2E: malloc (vg_replace_malloc.c:270) ==49159==by 0x402337: MAIN__ (test_leak.f90:55) ==49159==by 0x4026C9: main (test_leak.f90:36) ==49159== ==49159== LEAK SUMMARY: ==49159==definitely lost: 184,000 bytes in 4,000 blocks ==49159==indirectly lost: 0 bytes in 0 blocks ==49159== possibly lost: 0 bytes in 0 blocks ==49159==still reachable: 13,026 bytes in 1 blocks ==49159== suppressed: 0 bytes in 0 blocks ==49159== Reachable blocks (those to which a pointer was found) are not shown. ==49159== To see them, rerun with: --leak-check=full --show-reachable=yes ==49159== ==49159== For counts of detected and suppressed errors, rerun with: -v ==49159== ERROR SUMMARY: 2 errors from 2 contexts (suppressed: 8 from 6) Profiling timer expired
[Bug fortran/106771] New: [OOP] ICE with PACK intrinsic, in gfc_conv_expr_descriptor, at fortran/trans-array.c:7328
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106771 Bug ID: 106771 Summary: [OOP] ICE with PACK intrinsic, in gfc_conv_expr_descriptor, at fortran/trans-array.c:7328 Product: gcc Version: 9.2.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- I'm getting an ICE using the PACK intrinsic from within a polymorphic entity. There are several similar bugs reported, but none seems to address PACK, so I'm opening a new ticket. BTW: I've tested it on godbolt (try here: https://godbolt.org/z/cnj6PzqKz) And it looks like: WORKS on: 10.4.0, 11 (all), 12 (all) ICE on: 4.9, 5-8 (all), 9 (all), 10.1, 10.2, 10.3 The mask is created from a polymorphic elemental function on the object Here's a minimal example: module test implicit none type::t integer, allocatable :: iloc(:) contains procedure :: is_active => isa procedure :: list2loc => myfun_poly end type t contains elemental logical function isa(this,i) class(t), intent(in) :: this integer, intent(in) :: i if (i>0 .and. i<=merge(size(this%iloc),0,allocated(this%iloc))) then isa = this%iloc(i)>0 else isa = .false. endif end function isa ! internal compiler error: in gfc_conv_expr_descriptor, at fortran/trans-array.c:7328 function myfun_poly(this,IDs) result (ilocs) class(t), intent(in) :: this integer, intent(in) :: IDs(:) integer, allocatable :: ilocs(:) if (size(IDs)<=0) then allocate(ilocs(0)) else ilocs = pack(this%iloc(IDs),this%is_active(ilocs)) endif end function myfun_poly ! WORKS function myfun(this,IDs) result (ilocs) type(t), intent(in) :: this integer, intent(in) :: IDs(:) integer, allocatable :: ilocs(:) if (size(IDs)<=0) then allocate(ilocs(0)) else ilocs = pack(this%iloc(IDs),this%is_active(ilocs)) endif end function myfun end module test program testp use test implicit none type(t) :: a integer :: rnd(100) real :: x(100) integer, allocatable :: list(:) call random_number(x); rnd = ceiling(x*100) ! Works list = myfun(a,rnd) ! ICE list = a%list2loc(rnd) print *, 'list=',list end program testp Hope this helps, federico
[Bug fortran/106771] [OOP] ICE with PACK intrinsic, in gfc_conv_expr_descriptor, at fortran/trans-array.c:7328
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106771 --- Comment #3 from federico --- Right: here is a version where the object is initialized: https://godbolt.org/z/o566cPG8P I also see that for the versions that compile (e.g., 11.1.0), there's a weird SEGFAULT error at this line: elemental logical function isa(this,i) class(t), intent(in) :: this integer, intent(in) :: i integer :: n n = merge(size(this%iloc),0,allocated(this%iloc)) if (i>0 .and. i<=n) then ! Segmentation fault here isa = this%iloc(i)>0 else isa = .false. endif end function isa So it at least compiles, but apparently the bug is hidden somewhere else?
[Bug fortran/106771] [OOP] ICE with PACK intrinsic, in gfc_conv_expr_descriptor, at fortran/trans-array.c:7328
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106771 --- Comment #5 from federico --- My bad, the SEGFAULT is my mistake, I've made a half-baked example that does not work. Here's the fixed one: module test implicit none type::t integer, allocatable :: iloc(:) contains procedure :: is_active => isa procedure :: list2loc => myfun_poly end type t contains elemental logical function isa(this,i) class(t), intent(in) :: this integer, intent(in) :: i integer :: n n = merge(size(this%iloc),0,allocated(this%iloc)) if (i>0 .and. i<=n) then ! Segmentation fault here isa = this%iloc(i)>0 else isa = .false. endif end function isa ! internal compiler error: in gfc_conv_expr_descriptor, at fortran/trans-array.c:7328 function myfun_poly(this,IDs) result (ilocs) class(t), intent(in) :: this integer, intent(in) :: IDs(:) integer, allocatable :: ilocs(:) if (size(IDs)<=0) then allocate(ilocs(0)) else ilocs = pack(this%iloc(IDs),this%is_active(IDs)) endif end function myfun_poly ! WORKS function myfun(this,IDs) result (ilocs) type(t), intent(in) :: this integer, intent(in) :: IDs(:) integer, allocatable :: ilocs(:) if (size(IDs)<=0) then allocate(ilocs(0)) else ilocs = pack(this%iloc(IDs),this%is_active(IDs)) endif end function myfun end module test program testp use test implicit none type(t) :: a integer :: rnd(100),i real :: x(100) integer, allocatable :: list(:) ! Create a dummy initialization a%iloc = [(i,i=1,100)] call random_number(x); rnd = ceiling(x*99) ! Works print *, 'rnd=',rnd list = myfun(a,rnd) ! ICE list = a%list2loc(rnd) print *, 'list=',list end program testp The segfault is now gone, but the ICE remains for all versions until 10.3.0 (see https://godbolt.org/z/6TKa4sEe9)
[Bug fortran/106750] Memory leak calling array slice of derived type containing `allocatable` entries
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106750 --- Comment #3 from federico --- Thank you for checking this. So if I make the temporary array explicit, the leak goes away. In the case of the example i.e. 1) fixed-size and 2) very few elements are passed to the routine, it seems it would just be better to pass them as scalars, to avoid any temporaries from being at all created: j(i) = do_with_scalars(ts(choose(1)),ts(choose(2))) ! no more MEMORY LEAK
[Bug fortran/106790] New: Weird SIGSEV using polymorphic routine with "select type" and optimization (-O3)
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106790 Bug ID: 106790 Summary: Weird SIGSEV using polymorphic routine with "select type" and optimization (-O3) Product: gcc Version: 12.1.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- I'm getting a weird SIGSEV error when running the following code with full optimization (-O3). Error happens if: - type guard ("select type") is is "type is", no segfault if "class is" - the non-abstract derived type contains more than 1 scalar I suspect something is wrong with the compiler trying to optimize out the code in the main program (it's all constants). - Fails only on gfortran 11, 12. - Works on gfortran 7,8,9,10 Test it here: https://godbolt.org/z/qKPMvKnzf Here is the minimum working example: module ttt implicit none type, abstract :: t0 contains procedure(merge), deferred :: mergeWith procedure(pprint), deferred :: print end type type,extends(t0) :: t integer :: from1,to1,face contains procedure :: mergeWith => t_merge procedure :: print => link_print end type t abstract interface pure subroutine merge(this,that) import t0 class(t0), intent(inout) :: this class(t0), intent(in) :: that end subroutine merge function pprint(this) result(msg) import t0 class(t0), intent(in) :: this character(len=:), allocatable :: msg end function pprint end interface contains function link_print(this) result(msg) class(t), intent(in) :: this character(len=:), allocatable :: msg character(len=1024) :: buffer integer :: lt write(buffer,1) this%to1,this%from1,this%face lt = len_trim(buffer) allocate(character(len=lt) :: msg) if (lt>0) msg(1:lt) = buffer(1:lt) 1 format('to1=',i0,' from1=',i0,' face=',i0) end function link_print pure subroutine t_merge(this,that) class(t), intent(inout) :: this class(t0), intent(in) :: that select type (ttype => that) type is (t) ! Does not SIGSEV if using "class is (t)" ! SIGSEV at any of the following lines ! Does not crash anymore if commenting any of them if (this%to1<0 .and. this%from1<0) then this%to1 = ttype%to1 this%face = ttype%face end if end select end subroutine t_merge end module program test_t use ttt implicit none type(t) :: t1,t2 t1 = t(from1=123,to1=435,face=789) t2 = t(from1=-1,to1=-1,face=-1) call t1%mergeWith(t2) print *, 't1=',t1%print(),' t2=',t2%print() t1 = t(from1=123,to1=435,face=789) t2 = t(from1=-1,to1=-1,face=-1) ! Crash here on -O3, apparently during the unrolling of constants call t2%mergeWith(t1) print *, 't1=',t1%print(),' t2=',t2%print() end program Thanks, Federico
[Bug fortran/107157] New: Weird out-of-bounds error with multiple move_alloc's
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=107157 Bug ID: 107157 Summary: Weird out-of-bounds error with multiple move_alloc's Product: gcc Version: 12.1.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- I'm in trouble reducing this problem to a minimum viable example, so I'm asking for help - I have a nested derived type that contains allocatable components, like: type :: string character(len=1), allocatable :: t(:) end type string type :: data_point type(string) :: name real(real64), allocatable :: data(:) end type data_point type :: data_set type(data_point), allocatable :: data(:) end type data_set Now, I read in type(data_set) from several input files, and I grow that using a move_alloc, this way: subroutine read_dataset(this,fileName) class(data_set), intent(inout) :: this character(*), intent(in) :: fileName type(data_point), allocatable :: tmp(:) type(data_point) :: this_file [...] read_data: do n = n+1 ! Read one call this_file%read(blabla) ! Extend & copy allocate(tmp(n)) if (n>1) tmp(1:n-1) = this%data(1:n-1) tmp(n) = this_file call move_alloc(from=tmp,to=this%data) end do read_data end subroutine Starting from n>=2, after the routine exits, I have this error: ``` Fortran runtime error: Index '1' of dimension 1 of array '_F.DA0' outside of expected range (0:0) ``` - the error points to the end line of the module ("end module blabla") - I have no structures with that '_F.DA0' name, nor I can find anything like that in a text search in the .mod file (after unzipping it) - No error if move_alloc is called at most once I would like to reduce the problem to a simpler case I can post but I haven't been able to reproduce this so I'm asking for help: is there any compiler flags I can turn on to produce more output and/or understand better what's going on? Thank you in advance, Federico
[Bug fortran/107362] Segfault for recursive class
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=107362 federico changed: What|Removed |Added CC||federico.perini at gmail dot com --- Comment #2 from federico --- I'm getting the same issue on a recursive tree structure, I will post my testcase here instead of opening a new bug. I see a segfault in the default finalizer (I think it gets called when a recursive type is returned as a function result). I get the segfault on the default finalization routine with all gfortran versions, 7.1 to 12.1. This is also potentially linked to bug 106606 (in this case, the class is not polymorphic). Test program (also see on godbolt at: https://godbolt.org/z/PxYGhM8j9) module t type :: tree type(tree), allocatable :: node end type tree type :: container type(tree) :: root end type container contains type(container) function do_something() result(c) allocate(c%root%node) allocate(c%root%node%node) allocate(c%root%node%node%node) end function do_something end module t program test_function_output use t call create_and_finalize() contains subroutine create_and_finalize() type(container) :: c1,c2 c1 = do_something() c2 = c1 print *, 'allocated? 0 ',allocated(c1%root%node) print *, 'allocated? 1 ',allocated(c1%root%node%node) print *, 'allocated? 2 ',allocated(c1%root%node%node%node) end subroutine create_and_finalize end program test_function_output Thanks, Federico
[Bug fortran/107362] Internal compiler error for recursive class
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=107362 --- Comment #4 from federico --- OK I will report a new bug.
[Bug fortran/107489] New: Runtime segfault in finalization routine of derived type with allocatable components
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=107489 Bug ID: 107489 Summary: Runtime segfault in finalization routine of derived type with allocatable components Product: gcc Version: 12.1.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- I'm getting the same issue on a recursive tree structure. I see a segfault in the default finalizer (I think it gets called when a recursive type is returned as a function result). I get the segfault on the default finalization routine with all gfortran versions, 7.1 to 12.1. This is also potentially linked to bug 106606 (in this case, the class is not polymorphic). Test program (also see on godbolt at: https://godbolt.org/z/PxYGhM8j9) module t type :: tree type(tree), allocatable :: node end type tree type :: container type(tree) :: root end type container contains type(container) function do_something() result(c) allocate(c%root%node) allocate(c%root%node%node) allocate(c%root%node%node%node) end function do_something end module t program test_function_output use t call create_and_finalize() contains subroutine create_and_finalize() type(container) :: c1,c2 c1 = do_something() c2 = c1 print *, 'allocated? 0 ',allocated(c1%root%node) print *, 'allocated? 1 ',allocated(c1%root%node%node) print *, 'allocated? 2 ',allocated(c1%root%node%node%node) end subroutine create_and_finalize end program test_function_output Thanks, Federic
[Bug fortran/106731] ICE on automatic array of derived type with DTIO
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106731 --- Comment #11 from federico --- Thank you. I can confirm the patch works. I thought that, while fixing the issue, removing the assert was not the best solution as automatic arrays are not supposed to be static. My bad. Happy holidays, Federico
[Bug fortran/105558] New: simple 8-byte integer calculation fails with -O3 / march=core-avx2 on some gfortran 8/9/10 versions
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=105558 Bug ID: 105558 Summary: simple 8-byte integer calculation fails with -O3 / march=core-avx2 on some gfortran 8/9/10 versions Product: gcc Version: 10.3.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Created attachment 52950 --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=52950&action=edit integer(1) test program Hi gcc/gfortran team, I have two routines that encode and decode two integer(1) IDs (in [1:6] and [1:32] respectively) to a unique 8-byte integer(1), for 192 possible cases. The example that fails should behave like encode(1, 32) returns 77 decode(77) returns [1, 32] but returns either [-5, 33] or sometimes [3,71] With -O3, there are both versions and architectures of gfortran that either work or not. On godbolt (https://godbolt.org/z/5GboahWs1), this is what I see: gfortran | -O3 -mtune=generic | -O3 -march=core-avx2 | 12.1 |OK | OK | 11.3 |OK | OK | 11.2 |OK | OK | 11.1 |OK | OK | 10.3 |OK |ERROR | 10.2 |OK |ERROR | 10.1 |OK |ERROR | 9.4 |OK |ERROR | 9.3 |OK |ERROR | 9.2 |OK |ERROR | 9.1 |OK |ERROR | 8.5 | ERROR |ERROR | 8.4 | ERROR |ERROR | 8.3 | ERROR |ERROR | 8.2 | ERROR |ERROR | 8.1 | ERROR |ERROR | 7.3 |OK | OK | 7.2 |OK | OK | 7.1 |OK | OK | 6.3 |OK | OK | 5.5 |OK | OK | Also note that: - problem is with int8 only; all is OK with int16,int32,int64 - no problems with -O2. I'm attaching the code here as well, thank you, Federico
[Bug fortran/105558] simple 8-bit integer calculation fails with -O3 / march=core-avx2 on some gfortran 8/9/10 versions
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=105558 --- Comment #2 from federico --- Ok so we have: gfortran | [...] -fno-tree-vectorize | [...] -fno-vect-cost-model 10.3 |OK | ERROR 9.3 |OK | ERROR 8.3 |OK | ERROR
[Bug fortran/105558] simple 8-bit integer calculation fails with -O3 / march=core-avx2 on some gfortran 8/9/10 versions
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=105558 --- Comment #3 from federico --- -fno-vect-cost model also does not change behavior on gcc 11/7/6/5 (all OK)
[Bug fortran/78492] [OOP] Compiler segfault with non_overridable function in generic interface
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78492 --- Comment #5 from federico --- Created attachment 53145 --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=53145&action=edit test program: call non_overridable function from generic interface within polymorphic procedure
[Bug fortran/78492] [OOP] Compiler segfault with non_overridable function in generic interface
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78492 --- Comment #6 from federico --- I've attached a simple test program that confirms ICE on gfortran 11.3.0. ICE is returned only if - the non_overridable procedure is part of a generic type-bound interface - that same generic is being called from another type-bound procedure
[Bug fortran/106367] New: ICE in fold_convert_loc.c when referencing an array-of-structure-eleents from within a polymorphic function
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106367 Bug ID: 106367 Summary: ICE in fold_convert_loc.c when referencing an array-of-structure-eleents from within a polymorphic function Product: gcc Version: 11.3.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Created attachment 53321 --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=53321&action=edit test program I get an ICE with all gfortran versions from 5 to 12 when having a type-bound procedure that creates an array from some of its structure components. The error does not appear if the same command is called not within a function, or, the when the function argument is not polymorphic. The error (on 11.3.0) points to 31 | array = c%list%indices(c%v(1:)%flag) |1 internal compiler error: in fold_convert_loc, at fold-const.c:2440 This is a minimal program that reproduces the error. It was part of a far more complex structure: ``` module mymod implicit none type vert integer :: flag= 0 ! The fvm node flag (16 exploitable bits) end type vert type contnr type(vert), allocatable :: v(:) integer, allocatable :: list(:) contains procedure :: poly_get_list end type contnr contains ! Polymorphic function causes ICE function poly_get_list(c) result(array) class(contnr), intent(in) :: c integer, allocatable :: array(:) ! ICE internal compiler error: in fold_convert_loc, at fold-const.c:2440 (11.3.0) ! when this is put into a function array = c%list(c%v(1:)%flag) end function poly_get_list ! Non-polymorphic version works function get_list(c) result(array) type(contnr), intent(in) :: c integer, allocatable :: array(:) array = c%list(c%v(1:)%flag) end function get_list end module mymod program arrayOfStruct use mymod implicit none type(contnr) :: c integer :: i allocate(c%v(-1:100),c%list(-1:100)) forall(i=1:100) c%v(i)%flag = i c%list(i) = 100-i+1 end forall ! Direct: works! print "(*(1x,i0))", c%list(c%v(1:)%flag) ! Wrapped with TYPE(contnr): works! print "(*(1x,i0))", get_list(c) ! Wrapped with polymorphic CLASS(contnr): ICE ! Wrapped with TYPE(contnr): works! print "(*(1x,i0))", c%poly_get_list() end program arrayOfStruct ```
[Bug fortran/101757] New: Simple integer assigment fails (off-seted by -1) when compiling with -O3
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=101757 Bug ID: 101757 Summary: Simple integer assigment fails (off-seted by -1) when compiling with -O3 Product: gcc Version: 7.1.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Created attachment 51251 --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=51251&action=edit test program An extremely simple logical-flag-based assignment, which sets an integer to 1 if the logical is .true., and to 0 if .false., fails with gfortran 7.1.0 if compiled with -O3. Using `WHERE`, `MERGE`, or a simple loop does not change the result. Test program: program test_merge_ use iso_fortran_env implicit none integer, parameter :: N=1 logical :: test(N) integer :: i,itest(N) do i=1,N test(i) = mod(i,2)==0 end do itest = merge(1,0,test) print *, 'MERGE itest min (0) =',minval(itest),' max (1)=',maxval(itest) where (test) itest = 1 elsewhere itest = 0 end where print *, 'WHERE itest min (0) =',minval(itest),' max (1)=',maxval(itest) do i=1,N if (test(i)) then itest(i) = 1 else itest(i) = 0 endif end do print *, 'IFLOOP itest min (0) =',minval(itest),' max (1)=',maxval(itest) end program test_merge_ Expected result is OK if "-O2", wrong if "-O3": werc 1073% gfortran -O3 test_merge.f90 werc 1074% ./a.out MERGE itest min (0) = -1 max (1)= 0 WHERE itest min (0) = -1 max (1)= 0 IFLOOP itest min (0) = -1 max (1)= 0 werc 1075% gfortran -O2 test_merge.f90 werc 1076% ./a.out MERGE itest min (0) = 0 max (1)= 1 WHERE itest min (0) = 0 max (1)= 1 IFLOOP itest min (0) = 0 max (1)= 1 Tested OK on gfortran 9.2.0, 10.2.0, 10.3.0. Thanks, Federico
[Bug fortran/101757] Simple integer assigment fails (off-seted by -1) when compiling with -O3
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=101757 --- Comment #1 from federico --- Actually, the results are not "off-seted": whatever was to be set to 0 is properly set; values that should be set "+1" are given "-1" instead: itest(1)= 0 itest(2)=-1 test(1)= F test(2)= T Federico
[Bug fortran/101757] Simple integer assigment fails (off-seted by -1) when compiling with -O3
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=101757 --- Comment #2 from federico --- Tested on godbolt.org: https://godbolt.org/z/sPsdE6Y3W works on: 5.5, 6.3, all 10, all 11 error on: all 7, all 8, all 9
[Bug fortran/111952] New: Allocatable of derived type with DTIO is not deallocated going out of scope
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=111952 Bug ID: 111952 Summary: Allocatable of derived type with DTIO is not deallocated going out of scope Product: gcc Version: 13.2.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Test program: ``` module v public :: with_allocatable type, public :: t real :: r contains procedure, private :: wf generic :: write(formatted) => wf end type t contains subroutine wf(this, unit, iotype, v_list, iostat, iomsg) class(t), intent(in) :: this integer, intent(in) :: unit character(len=*), intent(in) :: iotype integer, intent(in) :: v_list(:) integer, intent(out) :: iostat character(len=*), intent(inout) :: iomsg end subroutine wf subroutine with_allocatable(n) integer, intent(in) :: n type(t), allocatable :: x(:) allocate(x(n)) end subroutine with_allocatable end module v program test use v call with_allocatable(10) call with_allocatable(10) ! crash end program ``` Upon the second call, the following runtime error is returned: ``` At line 22 of file /app/example.f90 Fortran runtime error: Attempting to allocate already allocated variable 'x' ``` I believe this may be related to bug 106731. On Compiler Explorer (https://godbolt.org/z/d3vfdhn6n), it seems like the issue is present also on gfortran versions prior to that fix.
[Bug fortran/115542] New: Invalid finalization in derived type containing allocatable entities
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=115542 Bug ID: 115542 Summary: Invalid finalization in derived type containing allocatable entities Product: gcc Version: 14.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Created attachment 58464 --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=58464&action=edit Finalization test program - Affected versions: gfortran >= 13 - MWE at: https://godbolt.org/z/rvP5qcvEz (also attached) - Possibly related: 110626 When a derived type has at least 3 layers: type(r) - type(q) - type(p) all types finalizable, and at least one "complex" component i.e. allocatable or real(real128), type finalization on the intermediate variables is wrongly called: - twice instead of once - the second time, I believe with a wrong memory address (or at least, with object data containing garbage). It's not in the MWE, but I have user cases where a pointer may become associated due to the invalid values in the second call, which triggers further issues and crashes (i.e. because the finalizer tries to deallocate it). In the attached program, there is an intent(out) argument so finalization should only be called once, as the subroutine enters: enter in-n-out r final ! ok: finalize parent type - q final F ! ok: finalize intermediate type - p final -1 ! ok: finalize 3rd-level scalars - p final -1 ! ok: finalize 3rd-level scalars - p final0 ! WRONG: 2nd-time and wrong value ERROR! ! WRONG: should not be called - p final0 ! WRONG: 2nd-time and wrong value ERROR! ! WRONG: should not be called hello world exit in-n-out Thank you, Federico
[Bug fortran/78492] [OOP] Compiler segfault with non_overridable function in generic interface
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78492 --- Comment #8 from federico --- Amazing, thank you!
[Bug fortran/114023] complex part%ref of complex named constant array cannot be used in an initialization expression.
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114023 federico changed: What|Removed |Added CC||federico.perini at gmail dot com --- Comment #4 from federico --- I've just stumbled upon this issue too. Nice to see that it had already been reported! I'm posting my MWE in case it may be useful to track down the issue: program test use iso_c_binding, only: c_loc,c_intptr_t,c_float complex(c_float), allocatable, target :: arr(:) real(c_float), pointer :: rreal(:),rimag(:) integer(c_intptr_t) :: stride_bytes arr = [(1,-1),(2,-2),(3,-3)] rreal => arr%re rimag => arr%im if (any(nint(rreal)/=[1,2,3])) stop 1 if (any(nint(rimag)/=-[1,2,3])) stop 2 if (is_contiguous(rreal)) stop 3 ! gfortran error if (is_contiguous(rimag)) stop 4 ! gfortran error ! Check internal pattern [re,im,re,im,...] stride_bytes = transfer(c_loc(rreal(2)),0_c_intptr_t) & -transfer(c_loc(rreal(1)),0_c_intptr_t) if (stride_bytes/=8_c_intptr_t) stop 5 end program test In this pointer example, both pointers's data is OK, but the pointer contiguity does not match the data pattern The test program can also be played with at the Compiler Explorer: https://godbolt.org/z/qKzo5Ydd4 Gfortran versions <9.3 cannot compile the example and report an ICE at gfc_get_dataptr_offset. Warm regards, Federico
[Bug tree-optimization/105558] simple 8-bit integer calculation fails with -O3 / march=core-avx2 on some gfortran 8/9/10 versions
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=105558 --- Comment #10 from federico --- Hi Sam, Thanks for looking into it - here is a simplified version of the test program: you can also test it live at the Compiler Explorer, at this link: https://godbolt.org/z/r63G348hM Thanks, Federico module subs use iso_fortran_env, only: ip => int8 implicit none contains ! from two indices in [1:6] and [1:32], create a unique int8 code elemental integer(ip) function ENCODE(i,j) integer(ip), intent(in) :: i ! loops in [1:6] range integer(ip), intent(in) :: j ! loops in [1:32] range integer(ip) :: k ENCODE = -122_ip + i do k=1_ip,j+1_ip ENCODE = ENCODE+6_ip end do end function ENCODE elemental subroutine DECODE(code,i,j) integer(ip), intent(in) :: code integer(ip), intent(out) :: i,j select case (code) case (-121_ip:82_ip) i = code j = -1_ip ! Child ID loop do while (i>-116_ip) j = j+1_ip i = i-6_ip end do i = i+122_ip case default i = -huge(i) j = -huge(j) end select end subroutine DECODE end module subs program test_int1 use iso_fortran_env, only: ip => int8 use subs implicit none integer(ip) :: i,j,code,id,jd logical :: success integer :: errors errors = 0 do j=1_ip,32_ip do i=1_ip,6_ip code = ENCODE(i,j) call DECODE(code,id,jd) if (i/=id .or. j/=jd) then errors = errors+1 print *, 'i=',i,' j=',j,' code=',code, & merge('error',' ',i/=id.or.j/=jd) endif end do end do success = errors==0 print *, merge('SUCCESS!','ERROR ',errors==0) if (errors>0) print "(*(i0,a))", errors,'/',6_ip*32_ip,' decoding errors ' end program test_int1
[Bug fortran/118580] Incorrect complex (sp) - real (dp) operation within maxval
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=118580 --- Comment #3 from federico --- Sorry, I introduced a typo while editing the post. Here is a slightly shorter version of the sample: ``` program complex_eye implicit none integer, parameter :: k = 2 integer :: j complex, dimension(k,k) :: A, B double precision :: eye(k, k), mx, mxB eye = 0 do j = 1,k eye(j,j) = 1 end do A = eye B = A - eye mx = maxval(abs(A-eye)) mxB = maxval(abs(B)) if (mx>1.0e-6) then write(*, *) "maxval(abs(A - eye)) = ", mx ! Should be 0, it is 1.0 write(*, *) "maxval(abs(B)) = ", mxB stop 1 else stop 0 endif end program complex_eye ```
[Bug fortran/118580] Incorrect complex (sp) - real (dp) operation within maxval
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=118580 --- Comment #7 from federico --- Thanks Harald and Steve, great hints. Looking at the `-fdump-tree-original`, I see: - the on-the-fly expression seems the difference between a complex(8) and a complex(4) expressions: ``` __builtin_cabs ( COMPLEX_EXPR <(real(kind=8)) REALPART_EXPR >, (real(kind=8)) IMAGPART_EXPR > > ! complex(8) -COMPLEX_EXPR ) ! complex(4) ``` double `cabs` is OK here I believe, and it is saved to `real(kind=8) limit.4;`. - when B is saved: ``` b[S.3 + D.3048] = COMPLEX_EXPR <(real(kind=4)) REALPART_EXPR >, (real(kind=8)) IMAGPART_EXPR >> -COMPLEX_EXPR > >, (real(kind=4)) IMAGPART_EXPR >, (real(kind=8)) IMAGPART_EXPR >> -COMPLEX_EXPR >>>; ``` The expression seems identical except there is a SAVE_EXPR and is then downgraded to a real(4) complex expression for saving into b (uses `__builtin_cabsf`).
[Bug fortran/118580] New: Incorrect complex (sp) - real (dp) operation within maxval
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=118580 Bug ID: 118580 Summary: Incorrect complex (sp) - real (dp) operation within maxval Product: gcc Version: 15.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Sample program: ``` program complex_eye implicit none integer, parameter :: dp = kind(0.d0) integer, parameter :: sp = kind(0.0) integer, parameter :: k = 2 integer :: i,j complex(sp), dimension(k,k) :: A, B real(dp) :: eye(k, k), mx, mxB do j = 1,k; do i=1, k eye(i,j) = merge(1,0,i==j) A(i,j) = merge(1,0,i==j) enddo B = A - eye mx = maxval(abs(A-eye)) mxB = maxval(abs(B)) if (mx>1.0e-6) then write(*, *) "maxval(abs(A - eye)) = ", mx ! Should be 0, it is 1.0 write(*, *) "maxval(abs(B)) = ", mxB stop 1 else stop 0 endif end program complex_eye ``` when `maxval` is run on a temporary expression, it returns a wrong value (often 1.0, but sometimes junk values). when the operation is saved in variable B first, it returns the correct value. In Compiler explorer, see https://godbolt.org/z/E6dWcEc9s : - fails on all versions of gfortran from 4.9.4 to 15.0 - fails with any optimization levels, also -O0 We found this issue after an update to the Fortran Standard Library, but the issue seems not related to the library itself. Thank you, Federico
[Bug fortran/119106] Crash with character array constructor + implicit loop + data from `parameter` variable
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=119106 --- Comment #1 from federico --- The `-fdump-tree-original` seems to highlight that: The `save`d variable data is accessed with unrolled indices [...] = n[(integer(kind=8)) i[0] + -1][1]{lb: 1 sz: 1}; The `parameter` variable data is accessed also unrolled, but instead of the unrolled indices (0, 1, 2, ...) there is `j`: [...] = p[(integer(kind=8)) i[(integer(kind=8)) j + -1] + -1][1]{lb: 1 sz: 1}; but `j` is undefined! So it would seem like for some reason, `j` has not been replaced by the unrolled index during the unrolling.
[Bug fortran/119106] New: Crash with character array constructor + implicit loop + data from `parameter` variable
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=119106 Bug ID: 119106 Summary: Crash with character array constructor + implicit loop + data from `parameter` variable Product: gcc Version: 15.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: federico.perini at gmail dot com Target Milestone: --- Created attachment 60649 --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=60649&action=edit Test program A runtime error is triggered with all versions of gfortran on this valid code: ``` program char_param_array implicit none character, parameter :: p(5) = ['1','2','3','4','5'] character, save :: n(5) = ['1','2','3','4','5'] integer :: i(10),j i = 4 print *, [(n(i(j)),j=1,10)] ! OK print *, [(p(i(j)),j=1,10)] ! runtime out-of-bounds error end program char_param_array ``` A slightly more refined test case is found at https://godbolt.org/z/ccroE47eh (Compiler Explorer). A runtime error from `-fcheck=bounds` shows an invalid loop variable, only if: - Implicit loop inside an array constructor - The character variable has the `parameter` attribute (no issue otherwise). Best regards, Federico