mirror of
git://gcc.gnu.org/git/gcc.git
synced 2025-04-22 11:41:07 +08:00
re PR fortran/25071 (dummy argument larger than actual argument)
2017-09-29 Dominique d'Humieres <dominiq@lps.ens.fr> PR fortran/25071 * gfortran.dg/argument_checking_3.f90: Change warnings to errors. * gfortran.dg/argument_checking_4.f90: Likewise. * gfortran.dg/argument_checking_5.f90: Likewise. * gfortran.dg/argument_checking_6.f90: Likewise. * gfortran.dg/argument_checking_10.f90: Likewise. * gfortran.dg/argument_checking_13.f90: Likewise. * gfortran.dg/argument_checking_15.f90: Likewise. * gfortran.dg/argument_checking_18.f90: Likewise. * gfortran.dg/gomp/udr8.f90: Likewise. * gfortran.dg/warn_argument_mismatch_1.f90: Add -std=legacy to the dg-options. From-SVN: r253287
This commit is contained in:
parent
37d92a7e0e
commit
1dce26a11d
@ -1,3 +1,18 @@
|
||||
2017-09-29 Dominique d'Humieres <dominiq@lps.ens.fr>
|
||||
|
||||
PR fortran/25071
|
||||
* gfortran.dg/argument_checking_3.f90: Change warnings to errors.
|
||||
* gfortran.dg/argument_checking_4.f90: Likewise.
|
||||
* gfortran.dg/argument_checking_5.f90: Likewise.
|
||||
* gfortran.dg/argument_checking_6.f90: Likewise.
|
||||
* gfortran.dg/argument_checking_10.f90: Likewise.
|
||||
* gfortran.dg/argument_checking_13.f90: Likewise.
|
||||
* gfortran.dg/argument_checking_15.f90: Likewise.
|
||||
* gfortran.dg/argument_checking_18.f90: Likewise.
|
||||
* gfortran.dg/gomp/udr8.f90: Likewise.
|
||||
* gfortran.dg/warn_argument_mismatch_1.f90: Add -std=legacy to
|
||||
the dg-options.
|
||||
|
||||
2017-09-29 Jakub Jelinek <jakub@redhat.com>
|
||||
|
||||
* g++.dg/ext/bitfield7.C: New test.
|
||||
|
@ -8,7 +8,7 @@ IMPLICIT NONE
|
||||
INTEGER :: i(-1:1)
|
||||
INTEGER :: j(-2:-1)
|
||||
CALL S(i)
|
||||
CALL S(j) ! { dg-warning "Actual argument contains too few elements for dummy argument 'i' .2/3." }
|
||||
CALL S(j) ! { dg-error "Actual argument contains too few elements for dummy argument 'i' .2/3." }
|
||||
CONTAINS
|
||||
SUBROUTINE S(i)
|
||||
INTEGER :: i(0:2)
|
||||
|
@ -53,8 +53,8 @@ call rlv2(pointer_dummy(1,1,1)) ! Valid F2003
|
||||
! We warn nonetheless as the result is not what is intented
|
||||
! and also formally wrong.
|
||||
! Using (1:string_length) would be ok.
|
||||
call rlv2(ptr(1,1,1)(1:1)) ! { dg-warning "contains too few elements" }
|
||||
call rlv2(assumed_sh_dummy(1,1,1)(1:2)) ! { dg-warning "contains too few elements" }
|
||||
call rlv2(ptr(1,1,1)(1:1)) ! { dg-error "contains too few elements" }
|
||||
call rlv2(assumed_sh_dummy(1,1,1)(1:2)) ! { dg-error "contains too few elements" }
|
||||
call rlv2(pointer_dummy(1,1,1)(1:3)) ! Valid F2003
|
||||
end
|
||||
|
||||
@ -72,12 +72,12 @@ character(2), pointer :: pointer_dummy(:,:,:)
|
||||
character(2), allocatable :: deferred(:,:,:)
|
||||
character(2), pointer :: ptr(:,:,:)
|
||||
call rlv3(deferred(1,1,1)) ! Valid since contiguous
|
||||
call rlv3(ptr(1,1,1)) ! { dg-warning "contains too few elements" }
|
||||
call rlv3(assumed_sh_dummy(1,1,1)) ! { dg-warning "contains too few elements" }
|
||||
call rlv3(pointer_dummy(1,1,1)) ! { dg-warning "contains too few elements" }
|
||||
call rlv3(ptr(1,1,1)) ! { dg-error "contains too few elements" }
|
||||
call rlv3(assumed_sh_dummy(1,1,1)) ! { dg-error "contains too few elements" }
|
||||
call rlv3(pointer_dummy(1,1,1)) ! { dg-error "contains too few elements" }
|
||||
|
||||
call rlv3(deferred(1,1,1)(1:2)) ! Valid since contiguous
|
||||
call rlv3(ptr(1,1,1)(1:2)) ! { dg-warning "contains too few elements" }
|
||||
call rlv3(assumed_sh_dummy(1,1,1)(1:2)) ! { dg-warning "contains too few elements" }
|
||||
call rlv3(pointer_dummy(1,1,1)(1:2)) ! { dg-warning "contains too few elements" }
|
||||
call rlv3(ptr(1,1,1)(1:2)) ! { dg-error "contains too few elements" }
|
||||
call rlv3(assumed_sh_dummy(1,1,1)(1:2)) ! { dg-error "contains too few elements" }
|
||||
call rlv3(pointer_dummy(1,1,1)(1:2)) ! { dg-error "contains too few elements" }
|
||||
end
|
||||
|
@ -14,20 +14,20 @@ character(len=4) :: str2(2,2)
|
||||
|
||||
call test()
|
||||
|
||||
call foo(i(8)) ! { dg-warning "too few elements for dummy argument 'a' .3/4." }
|
||||
call foo(i(8)) ! { dg-error "too few elements for dummy argument 'a' .3/4." }
|
||||
call foo(j(1,1))
|
||||
call foo(j(2,1)) ! { dg-warning "too few elements for dummy argument 'a' .3/4." }
|
||||
call foo(j(1,2)) ! { dg-warning "too few elements for dummy argument 'a' .2/4." }
|
||||
call foo(j(2,1)) ! { dg-error "too few elements for dummy argument 'a' .3/4." }
|
||||
call foo(j(1,2)) ! { dg-error "too few elements for dummy argument 'a' .2/4." }
|
||||
|
||||
str = 'FORT'
|
||||
str2 = 'fort'
|
||||
call bar(str(:)(1:2)) ! { dg-warning "too few elements for dummy argument 'c' .4/6." }
|
||||
call bar(str(1:2)(1:1)) ! { dg-warning "too few elements for dummy argument 'c' .2/6." }
|
||||
call bar(str(2)) ! { dg-warning "too few elements for dummy argument 'c' .4/6." }
|
||||
call bar(str(:)(1:2)) ! { dg-error "too few elements for dummy argument 'c' .4/6." }
|
||||
call bar(str(1:2)(1:1)) ! { dg-error "too few elements for dummy argument 'c' .2/6." }
|
||||
call bar(str(2)) ! { dg-error "too few elements for dummy argument 'c' .4/6." }
|
||||
call bar(str(1)(2:1)) ! OK
|
||||
call bar(str2(2,1)(4:1)) ! OK
|
||||
call bar(str2(1,2)(3:4)) ! OK
|
||||
call bar(str2(1,2)(4:4)) ! { dg-warning "too few elements for dummy argument 'c' .5/6." }
|
||||
call bar(str2(1,2)(4:4)) ! { dg-error "too few elements for dummy argument 'c' .5/6." }
|
||||
contains
|
||||
subroutine foo(a)
|
||||
integer :: a(4)
|
||||
|
@ -14,8 +14,8 @@
|
||||
|
||||
tt%j = i
|
||||
|
||||
call sub1 (i) ! { dg-warning "Actual argument contains too few elements" }
|
||||
call sub1 (tt%j) ! { dg-warning "Actual argument contains too few elements" }
|
||||
call sub1 (i) ! { dg-error "Actual argument contains too few elements" }
|
||||
call sub1 (tt%j) ! { dg-error "Actual argument contains too few elements" }
|
||||
call sub2 (i) ! { dg-error "Rank mismatch in argument" }
|
||||
call sub2 (tt%j) ! { dg-error "Rank mismatch in argument" }
|
||||
|
||||
|
@ -25,12 +25,12 @@ end interface
|
||||
call foo(len2) ! { dg-error "Rank mismatch in argument" }
|
||||
call foo("ca") ! { dg-error "Rank mismatch in argument" }
|
||||
call bar("ca") ! { dg-error "Rank mismatch in argument" }
|
||||
call foobar(len2) ! { dg-warning "contains too few elements" }
|
||||
call foobar(len2) ! { dg-error "contains too few elements" }
|
||||
call foobar(len4)
|
||||
call foobar("bar") ! { dg-warning "contains too few elements" }
|
||||
call foobar("bar") ! { dg-error "contains too few elements" }
|
||||
call foobar("bar33")
|
||||
call arr(len2) ! { dg-warning "contains too few elements" }
|
||||
call arr(len2) ! { dg-error "contains too few elements" }
|
||||
call arr(len4)
|
||||
call arr("bar") ! { dg-warning "contains too few elements" }
|
||||
call arr("bar") ! { dg-error "contains too few elements" }
|
||||
call arr("bar33")
|
||||
end program test
|
||||
|
@ -12,10 +12,10 @@ interface
|
||||
end subroutine arr
|
||||
end interface
|
||||
|
||||
call foobar( [ "bar" ]) ! { dg-warning "contains too few elements" }
|
||||
call foobar( [ "bar" ]) ! { dg-error "contains too few elements" }
|
||||
call foobar( ["ba ","r33"])
|
||||
call arr( [ "bar" ]) ! { dg-warning "contains too few elements" }
|
||||
call arr( [ "bar" ]) ! { dg-error "contains too few elements" }
|
||||
call arr( reshape(["b","a","r","3"], [2,2]))
|
||||
call arr( reshape(["b","a"], [1,2])) ! { dg-warning "contains too few elements" }
|
||||
call arr( reshape(["b","a"], [2,1])) ! { dg-warning "contains too few elements" }
|
||||
call arr( reshape(["b","a"], [1,2])) ! { dg-error "contains too few elements" }
|
||||
call arr( reshape(["b","a"], [2,1])) ! { dg-error "contains too few elements" }
|
||||
end program test
|
||||
|
@ -13,23 +13,23 @@ interface
|
||||
end interface
|
||||
|
||||
integer a(3), b(5)
|
||||
call foobar(a) ! { dg-warning "contains too few elements" }
|
||||
call foobar(a) ! { dg-error "contains too few elements" }
|
||||
call foobar(b)
|
||||
call foobar(b(1:3)) ! { dg-warning "contains too few elements" }
|
||||
call foobar(b(1:3)) ! { dg-error "contains too few elements" }
|
||||
call foobar(b(1:5))
|
||||
call foobar(b(1:5:2)) ! { dg-warning "contains too few elements" }
|
||||
call foobar(b(1:5:2)) ! { dg-error "contains too few elements" }
|
||||
call foobar(b(2))
|
||||
call foobar(b(3)) ! { dg-warning "Actual argument contains too few elements" }
|
||||
call foobar(reshape(a(1:3),[2,1])) ! { dg-warning "contains too few elements" }
|
||||
call foobar(b(3)) ! { dg-error "Actual argument contains too few elements" }
|
||||
call foobar(reshape(a(1:3),[2,1])) ! { dg-error "contains too few elements" }
|
||||
call foobar(reshape(b(2:5),[2,2]))
|
||||
|
||||
call arr(a) ! { dg-warning "contains too few elements" }
|
||||
call arr(a) ! { dg-error "contains too few elements" }
|
||||
call arr(b)
|
||||
call arr(b(1:3)) ! { dg-warning "contains too few elements" }
|
||||
call arr(b(1:3)) ! { dg-error "contains too few elements" }
|
||||
call arr(b(1:5))
|
||||
call arr(b(1:5:2)) ! { dg-warning "contains too few elements" }
|
||||
call arr(b(1:5:2)) ! { dg-error "contains too few elements" }
|
||||
call arr(b(2))
|
||||
call arr(b(3)) ! { dg-warning "contains too few elements" }
|
||||
call arr(reshape(a(1:3),[2,1])) ! { dg-warning "contains too few elements" }
|
||||
call arr(b(3)) ! { dg-error "contains too few elements" }
|
||||
call arr(reshape(a(1:3),[2,1])) ! { dg-error "contains too few elements" }
|
||||
call arr(reshape(b(2:5),[2,2]))
|
||||
end program test
|
||||
|
@ -14,7 +14,7 @@ real,dimension(-1:2) :: z
|
||||
call sub(x(:))
|
||||
call sub(y(:))
|
||||
call sub(z(:))
|
||||
call sub(w(:)) ! { dg-warning "too few elements" }
|
||||
call sub(w(:)) ! { dg-error "too few elements" }
|
||||
|
||||
contains
|
||||
subroutine sub(a)
|
||||
|
@ -274,11 +274,11 @@ subroutine test13
|
||||
use m
|
||||
!$omp declare reduction (foo : integer : omp_out = omp_out + omp_in) initializer (omp_priv = 0)
|
||||
!$omp declare reduction (bar : integer : omp_out = & ! { dg-error "Different shape for array assignment at \[^\n\r]* on dimension 1 .9 and 10" }
|
||||
!$omp & fn5 (omp_out, omp_in)) & ! { dg-warning "Actual argument contains too few elements for dummy argument \[^\n\r]* .9/10" }
|
||||
!$omp & initializer (sub5 (omp_priv, omp_orig)) ! { dg-warning "Actual argument contains too few elements for dummy argument \[^\n\r]* .9/10" }
|
||||
!$omp declare reduction (baz : integer : sub6 (omp_out, omp_in)) & ! { dg-warning "Actual argument contains too few elements for dummy argument \[^\n\r]* .9/10" }
|
||||
!$omp & fn5 (omp_out, omp_in)) & ! { dg-error "Actual argument contains too few elements for dummy argument \[^\n\r]* .9/10" }
|
||||
!$omp & initializer (sub5 (omp_priv, omp_orig)) ! { dg-error "Actual argument contains too few elements for dummy argument \[^\n\r]* .9/10" }
|
||||
!$omp declare reduction (baz : integer : sub6 (omp_out, omp_in)) & ! { dg-error "Actual argument contains too few elements for dummy argument \[^\n\r]* .9/10" }
|
||||
!$omp initializer (omp_priv = & ! { dg-error "Different shape for array assignment at \[^\n\r]* on dimension 1 .9 and 10" }
|
||||
!$omp & fn6 (omp_orig)) ! { dg-warning "Actual argument contains too few elements for dummy argument \[^\n\r]* .9/10" }
|
||||
!$omp & fn6 (omp_orig)) ! { dg-error "Actual argument contains too few elements for dummy argument \[^\n\r]* .9/10" }
|
||||
integer :: a(9)
|
||||
!$omp parallel reduction (foo : a)
|
||||
!$omp end parallel
|
||||
|
@ -1,5 +1,5 @@
|
||||
! { dg-do compile }
|
||||
! { dg-options "-Wno-argument-mismatch" }
|
||||
! { dg-options "-std=legacy -Wno-argument-mismatch" }
|
||||
!
|
||||
! No warnings should be output here with -Wno-argument-mismatch.
|
||||
!
|
||||
|
Loading…
x
Reference in New Issue
Block a user