[Bug fortran/99709] New: VALUE attribute for an object with nonconstant length parameter
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=99709 Bug ID: 99709 Summary: VALUE attribute for an object with nonconstant length parameter Product: gcc Version: 10.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: xiao@compiler-dev.com Target Milestone: --- The extensions to VALUE attribute(f2008) permitted for an object with a nonconstant length parameter, but the result of the following test case is same with none VALUE attribute. program value_f2008 implicit none type :: matrix(k) integer, len :: k integer :: elements(k, k) !integer :: elements(2, 2) end type matrix type, extends(matrix) :: child end type child type(child(2)) :: obj obj%elements = reshape([1, 2, 3, 4], shape(obj%elements)) call test_value_attr(2, obj) print *, obj%elements contains subroutine test_value_attr(n, nonconstant_length_object) integer :: n type(child(n)), value :: nonconstant_length_object nonconstant_length_object%elements = 0 end subroutine test_value_attr end program value_f2008 The result is 0 0 0 0
[Bug fortran/100110] New: Parameterized Derived Types, problems with global variable
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=100110 Bug ID: 100110 Summary: Parameterized Derived Types, problems with global variable Product: gcc Version: 10.1.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: xiao@compiler-dev.com Target Milestone: --- the test case is, program p implicit none type t(n) integer, len :: n integer :: arr(n, n) end type type(t(2)) :: obj print *, obj%n print *, shape(obj%arr) call test() contains subroutine test() print *, obj%n print *, shape(obj%arr) end subroutine end program expected result is 2 2 2 2 2 2 but is 0 0 0 0 0 0
[Bug fortran/98307] New: use "allocatable" instead of "pointer" (forall_3.f90)
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98307 Bug ID: 98307 Summary: use "allocatable" instead of "pointer" (forall_3.f90) Product: gcc Version: 10.1.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: xiao@compiler-dev.com Target Milestone: --- in the test case "gfortran.fortran-torture/execute/forall_3.f90", if replace "pointer" with "allocatable", the result will be different. program evil_forall implicit none type t logical valid integer :: s !integer, dimension(:), pointer :: p integer, dimension(:), allocatable :: p end type type (t), dimension (5) :: v integer i allocate (v(1)%p(2)) allocate (v(2)%p(8)) !v(3)%p => NULL() allocate (v(4)%p(8)) allocate (v(5)%p(2)) v(:)%valid = (/.true., .true., .false., .true., .true./) v(:)%s = (/1, 8, 999, 6, 2/) v(1)%p(:) = (/9, 10/) v(2)%p(:) = (/1, 2, 3, 4, 5, 6, 7, 8/) v(4)%p(:) = (/13, 14, 15, 16, 17, 18, 19, 20/) v(5)%p(:) = (/11, 12/) forall (i=1:5,v(i)%valid) v(i)%p(1:v(i)%s) = v(6-i)%p(1:v(i)%s) end forall if (any(v(1)%p(:) .ne. (/11, 10/))) STOP 1 if (any(v(2)%p(:) .ne. (/13, 14, 15, 16, 17, 18, 19, 20/))) STOP 2 if (any(v(4)%p(:) .ne. (/1, 2, 3, 4, 5, 6, 19, 20/))) STOP 3 if (any(v(5)%p(:) .ne. (/9, 10/))) STOP 4 ! I should really free the memory I've allocated. end program the result is "STOP 3"
[Bug fortran/98458] New: implied do-loop used in initialization with RESHAPE throw ICE
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98458 Bug ID: 98458 Summary: implied do-loop used in initialization with RESHAPE throw ICE Product: gcc Version: 10.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: xiao@compiler-dev.com Target Milestone: --- test case: program test implicit none integer :: i integer, parameter :: t(6) = [1,2,3,4,5,6] integer, parameter :: tmp(6,1) = reshape([(t(i:i+1),i=1,3)],[6,1]) print *, tmp end result: 6 | print *, tmp | internal compiler error: in gfc_conv_array_initializer, at fortran/trans-array.c:6162
[Bug fortran/98458] PRINT the array constructed from implied do-loop throw ICE
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98458 --- Comment #5 from xiao@compiler-dev.com --- (In reply to Paul Thomas from comment #4) > Created attachment 49856 [details] > Fix for the PR > > Thank you for the report on this problem. > > The attached patch fixes the problem and regression tests OK. I need to do a > bit more thinking about it because I was unable to find a point in general > expression simplification where the fix could be applied. Instead, it only > seems to work in the simplification of intrinsic functions. Fortunately, > this seems to be the only place where it is needed. > > Paul As a beginner of FORTRAN, I am not sure about the result of implied do-loop which contains array section, so add "print" to check. Thanks for your attention on this problem.
[Bug fortran/98948] New: unexpected error in procedure pointer initialization or assignment with intrinsic
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98948 Bug ID: 98948 Summary: unexpected error in procedure pointer initialization or assignment with intrinsic Product: gcc Version: 10.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: xiao@compiler-dev.com Target Milestone: --- the test case is: program test implicit none procedure(real*4), pointer :: pf => ABS print *, pf(-6.5_4) if(pf(-6.5_4) /= ABS(-6.5_4)) STOP 1 pf => ACOS print *, pf(0.54030231_4) if(pf(0.54030231_4) /= ACOS(0.54030231_4)) STOP 2 print *, 'PASS' end program the error under gfortran 10.0 is: bbb.f90:3:41: 3 | procedure(real*4), pointer :: pf => ABS | 1 Error: Symbol ‘abs’ at (1) has no IMPLICIT type bbb.f90:8:12: 8 | pf => ACOS |1 Error: Symbol ‘acos’ at (1) has no IMPLICIT type If annotate those two if-stmt, the test case will function well. And the result is: 6.5000 0.99940 PASS
[Bug fortran/100555] New: [OPENMP] ICE in target parallel construct with if-clause
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=100555 Bug ID: 100555 Summary: [OPENMP] ICE in target parallel construct with if-clause Product: gcc Version: 10.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: xiao@compiler-dev.com Target Milestone: --- The test case is, program test use omp_lib integer :: i i = 1 !!$omp target parallel if(target: i > 0) if(parallel: i > 0) !ICE !!$omp target parallel if(target: i > 0) !!$omp target parallel if(parallel: i > 0) !ICE !!$omp target parallel if(i > 0) !ICE !$omp target parallel print *, "thread id = ", omp_get_thread_num() !$omp end target parallel end program It seems that when exist if-clause applies to parallel directive, there is an ICE. If change target parallel construct to target parallel loop construct, there is no ICE.
[Bug fortran/100555] [OPENMP] ICE in target parallel construct with if-clause
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=100555 --- Comment #1 from xiao@compiler-dev.com --- Additionally, "implicit none" will lead errors if exists directive-name-modifier in if-clause. module m integer, save :: n = 4 end module program test use m use omp_lib implicit none integer :: i !$omp target parallel do if(target: n > 2) if(parallel: n > 2) do i=1,n print *, "thread id = ", omp_get_thread_num() end do !$omp end target parallel do end program The error is, test.f90:10:54: 10 | !$omp target parallel do if(target: n > 2) if(parallel: n > 2) | 1 Error: Symbol ‘parallel’ at (1) has no IMPLICIT type; did you mean ‘omp_in_parallel’? test.f90:10:34: 10 | !$omp target parallel do if(target: n > 2) if(parallel: n > 2) | 1 Error: Symbol ‘target’ at (1) has no IMPLICIT type
[Bug fortran/101079] New: [OPENMP] The value of list-item in linear clause in loop construct is not calculated on each iteration
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=101079 Bug ID: 101079 Summary: [OPENMP] The value of list-item in linear clause in loop construct is not calculated on each iteration Product: gcc Version: 10.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: xiao@compiler-dev.com Target Milestone: --- The testcase is, program p use omp_lib integer :: i, j j = 0 !$omp parallel num_threads(2) !$omp do linear(j:1) schedule(static, 4) do i= 1, 10 print *, i, j, omp_get_thread_num() end do !$omp end parallel print *, "final j: ", j end program The result is, 1 0 0 2 0 0 3 0 0 4 0 0 9 8 0 10 8 0 5 4 1 6 4 1 7 4 1 8 4 1 final j:8 It looks like that the calculation for list-item 'j' is invoked after task dispatching not on each iteration. See OpenMP 4.5 specification, 2.15.3.7 "When a linear clause is specified on a construct, the value of the new list item on each iteration of the associated loop(s) corresponds to the value of the original list item before entering the construct plus the logical number of the iteration times linear-step. The value corresponding to the sequentially last iteration of the associated loop(s) is assigned to the original list item." The expected result seems to be that 'j' always equals (i-1), and final j equals 9.
[Bug fortran/101079] [OPENMP] The value of list-item in linear clause in loop construct is not calculated on each iteration
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=101079 --- Comment #2 from xiao@compiler-dev.com --- (In reply to Jakub Jelinek from comment #1) > Under discussions in OpenMP language committee, but the latest proposal is > that this is invalid, you need to increment the linear variable by > linear-step in the body of the construct. If that is voted into 5.2, we > won't be changing GCC for this which always assumed that is the case. Not > incrementing it in the body means that the testcase will behave > significantly differently with -fno-openmp, and also result in worse > generated code for many cases that do increment the linear variables. Thanks for your reply. Indeed, all the testcases I have came across about linear clause within loop construct have the increment for linear variable in loop body, but mostly testcases about linear clause within simd construct don't. Could you help to confirm whether linear clause within simd construct is handled correctly in the following testcase? program p integer, parameter :: M = 1 integer :: b integer :: c(M), i b = 10 !$omp simd linear(b:5) do i = 1, M c(i) = b end do print *, c(1), c(2), c(3), c(4), c(M) print *, "final b:", b end program When compile with option -O0, the output is, 10 10 10 10 10 final b: 10 when compile with option -O1, -O2, -O3 or -Os, the output is, 10 15 20 25 50005 final b: 50005
[Bug fortran/101079] [OPENMP] The value of list-item in linear clause in loop construct is not calculated on each iteration
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=101079 --- Comment #3 from xiao@compiler-dev.com --- (In reply to Jakub Jelinek from comment #1) > Under discussions in OpenMP language committee, but the latest proposal is > that this is invalid, you need to increment the linear variable by > linear-step in the body of the construct. If that is voted into 5.2, we > won't be changing GCC for this which always assumed that is the case. Not > incrementing it in the body means that the testcase will behave > significantly differently with -fno-openmp, and also result in worse > generated code for many cases that do increment the linear variables. Please ignore the comment 2, the testcase contained in is also wrong, an increment should be added as the last statement in the loop body.
[Bug fortran/101079] [OPENMP] The value of list-item in linear clause in loop construct is not calculated on each iteration
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=101079 --- Comment #4 from xiao@compiler-dev.com --- (In reply to Jakub Jelinek from comment #1) > Under discussions in OpenMP language committee, but the latest proposal is > that this is invalid, you need to increment the linear variable by > linear-step in the body of the construct. If that is voted into 5.2, we > won't be changing GCC for this which always assumed that is the case. Not > incrementing it in the body means that the testcase will behave > significantly differently with -fno-openmp, and also result in worse > generated code for many cases that do increment the linear variables. Hi Jakub, can you tell me where they discuss the proposal? I am very interested in the new features introduced from version 4.5, especially the implementation in the compiler.
[Bug fortran/101079] [OPENMP] The value of list-item in linear clause in loop construct is not calculated on each iteration
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=101079 --- Comment #6 from xiao@compiler-dev.com --- (In reply to Jakub Jelinek from comment #5) > OpenMP language committee discussions aren't public, there will be soon an > OpenMP 5.2 public draft though. > The particular restriction under discussion is: > "For a linear clause that appears on a loop-associated construct, > the difference between the value of a list item at the end of a logical > iteration and its value at the beginning of the logical iteration must > be equal to linear-step." Thanks.
[Bug fortran/103914] New: -fcheck=do: Problems with omp parallel do construct
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103914 Bug ID: 103914 Summary: -fcheck=do: Problems with omp parallel do construct Product: gcc Version: 10.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: xiao@compiler-dev.com Target Milestone: --- The test case do.f90: program test integer :: i !$omp parallel do do i = 1, 10 call foo(i) end do !$omp end parallel do contains subroutine foo(i) integer :: i i = i + 3 end subroutine end program test When compile it with "gfortran do.f90 -fcheck=do" run a.out, error message is: At line 4 of file do.f90 Fortran runtime error: Loop variable has been modified When compile it with "gfortran do.f90 -fcheck=do -fopenmp" run a.out, no runtime error occur. I have some questions: why the option "-fcheck=do" do not take effect for "parallel do"? Should the option "-fcheck=do" take effect for "parallel do"?
[Bug fortran/103914] -fcheck=do seems not to work with omp parallel do construct
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103914 --- Comment #2 from xiao@compiler-dev.com --- Thanks a lot.
[Bug fortran/103914] -fcheck=do seems not to work with omp parallel do construct
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103914 --- Comment #3 from xiao@compiler-dev.com --- (In reply to xiao@compiler-dev.com from comment #2) > Thanks a lot. (In reply to anlauf from comment #1) > (In reply to xiao@compiler-dev.com from comment #0) > > I have some questions: > > why the option "-fcheck=do" do not take effect for "parallel do"? > > Just an observation: > > The code for ordinary do loops is generated in gfc_trans_do(), which also > adds code for runtime checking. > > The code for OpenMP annotated loops is generated in gfc_trans_omp_do(). > There appears to be no runtime checking implemented for this type of loops. Thanks a lot.
[Bug fortran/103342] New: [OPENMP]Missing barrier for linear clause within loop simd construct which not directly contained by parrellel construct
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103342 Bug ID: 103342 Summary: [OPENMP]Missing barrier for linear clause within loop simd construct which not directly contained by parrellel construct Product: gcc Version: 10.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: xiao@compiler-dev.com Target Milestone: --- The test case is, program p integer, parameter :: N = 1 integer :: a(N) integer :: i, j j = 0 !$omp parallel do simd linear(j: 2) do i = 1, N a(i) = a(i) + j j = j + 2 enddo j = 0 !$omp parallel call subr(a) !$omp end parallel contains subroutine subr(x) integer :: x(N) !$omp do simd linear(j: 2) do i = 1, N x(i) = x(i) + j j = j + 2 enddo end subroutine end program After complier with, gfortran-10 test.f90 -fopenmp -fdump-tree-all In the file test.f90.007t.omplower, I found "builtin_GOMP_barrier" in "p", but none in "subr". And when I convert to C-style testcase, found "builtin_GOMP_barrier" in both. Except the missing of barrier, there is an ICE for gfortran when removed "simd" in "subr".
[Bug fortran/106100] New: where
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106100 Bug ID: 106100 Summary: where Product: gcc Version: 10.0 Status: UNCONFIRMED Severity: normal Priority: P3 Component: fortran Assignee: unassigned at gcc dot gnu.org Reporter: xiao@compiler-dev.com Target Milestone: ---