summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg')
-rw-r--r--gcc/testsuite/gfortran.dg/char4_iunit_1.f032
-rw-r--r--gcc/testsuite/gfortran.dg/cshift_1.f90108
-rw-r--r--gcc/testsuite/gfortran.dg/cshift_2.f90152
-rw-r--r--gcc/testsuite/gfortran.dg/debug/pr35154-stabs.f2
-rw-r--r--gcc/testsuite/gfortran.dg/fmt_pf.f902
-rw-r--r--gcc/testsuite/gfortran.dg/guality/pr41558.f902
-rw-r--r--gcc/testsuite/gfortran.dg/implicit_class_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/init_flag_10.f902
-rw-r--r--gcc/testsuite/gfortran.dg/init_flag_3.f902
-rw-r--r--gcc/testsuite/gfortran.dg/int_conv_2.f902
-rw-r--r--gcc/testsuite/gfortran.dg/isnan_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/isnan_2.f902
-rw-r--r--gcc/testsuite/gfortran.dg/large_real_kind_2.F902
-rw-r--r--gcc/testsuite/gfortran.dg/maxloc_2.f902
-rw-r--r--gcc/testsuite/gfortran.dg/maxlocval_2.f902
-rw-r--r--gcc/testsuite/gfortran.dg/maxlocval_4.f902
-rw-r--r--gcc/testsuite/gfortran.dg/minloc_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/minlocval_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/minlocval_4.f902
-rw-r--r--gcc/testsuite/gfortran.dg/module_nan.f902
-rw-r--r--gcc/testsuite/gfortran.dg/namelist_42.f902
-rw-r--r--gcc/testsuite/gfortran.dg/namelist_43.f902
-rw-r--r--gcc/testsuite/gfortran.dg/nan_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/nan_2.f902
-rw-r--r--gcc/testsuite/gfortran.dg/nan_3.f902
-rw-r--r--gcc/testsuite/gfortran.dg/nan_4.f902
-rw-r--r--gcc/testsuite/gfortran.dg/nan_5.f902
-rw-r--r--gcc/testsuite/gfortran.dg/nan_6.f902
-rw-r--r--gcc/testsuite/gfortran.dg/nan_7.f902
-rw-r--r--gcc/testsuite/gfortran.dg/nearest_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/nearest_3.f902
-rw-r--r--gcc/testsuite/gfortran.dg/pr20257.f902
-rw-r--r--gcc/testsuite/gfortran.dg/pr47614.f2
-rw-r--r--gcc/testsuite/gfortran.dg/pr68078.f902
-rw-r--r--gcc/testsuite/gfortran.dg/proc_ptr_comp_51.f9036
-rw-r--r--gcc/testsuite/gfortran.dg/read_infnan_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/real_const_3.f902
-rw-r--r--gcc/testsuite/gfortran.dg/realloc_on_assign_2.f032
-rw-r--r--gcc/testsuite/gfortran.dg/scratch_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/stat_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/stat_2.f902
-rw-r--r--gcc/testsuite/gfortran.dg/transfer_simplify_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/typebound_operator_9.f032
-rw-r--r--gcc/testsuite/gfortran.dg/vect/fast-math-pr38968.f902
44 files changed, 337 insertions, 41 deletions
diff --git a/gcc/testsuite/gfortran.dg/char4_iunit_1.f03 b/gcc/testsuite/gfortran.dg/char4_iunit_1.f03
index 7d388ad99fe..0c7b70e45b9 100644
--- a/gcc/testsuite/gfortran.dg/char4_iunit_1.f03
+++ b/gcc/testsuite/gfortran.dg/char4_iunit_1.f03
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
! PR37077 Implement Internal Unit I/O for character KIND=4
! Test case prepared by Jerry DeLisle <jvdelisle@gcc.gnu.org>
program char4_iunit_1
diff --git a/gcc/testsuite/gfortran.dg/cshift_1.f90 b/gcc/testsuite/gfortran.dg/cshift_1.f90
new file mode 100644
index 00000000000..e2024ea99dd
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/cshift_1.f90
@@ -0,0 +1,108 @@
+! { dg-do run }
+! Take cshift through its paces to make sure no boundary
+! cases are wrong.
+
+module kinds
+ integer, parameter :: sp = selected_real_kind(6) ! Single precision
+end module kinds
+
+module replacements
+ use kinds
+contains
+ subroutine cshift_sp_3_v1 (array, shift, dim, res)
+ integer, parameter :: wp = sp
+ real(kind=wp), dimension(:,:,:), intent(in) :: array
+ integer, intent(in) :: shift, dim
+ real(kind=wp), dimension(:,:,:), intent(out) :: res
+ integer :: i,j,k
+ integer :: sh, rsh
+ integer :: n
+ integer :: n2, n3
+ res = 0
+ n3 = size(array,3)
+ n2 = size(array,2)
+ n1 = size(array,1)
+ if (dim == 1) then
+ n = n1
+ sh = modulo(shift, n)
+ rsh = n - sh
+ do k=1, n3
+ do j=1, n2
+ do i=1, rsh
+ res(i,j,k) = array(i+sh,j,k)
+ end do
+ do i=rsh+1,n
+ res(i,j,k) = array(i-rsh,j,k)
+ end do
+ end do
+ end do
+ else if (dim == 2) then
+ n = n2
+ sh = modulo(shift,n)
+ rsh = n - sh
+ do k=1, n3
+ do j=1, rsh
+ do i=1, n1
+ res(i,j,k) = array(i,j+sh, k)
+ end do
+ end do
+ do j=rsh+1, n
+ do i=1, n1
+ res(i,j,k) = array(i,j-rsh, k)
+ end do
+ end do
+ end do
+ else if (dim == 3) then
+ n = n3
+ sh = modulo(shift, n)
+ rsh = n - sh
+ do k=1, rsh
+ do j=1, n2
+ do i=1, n1
+ res(i,j,k) = array(i, j, k+sh)
+ end do
+ end do
+ end do
+ do k=rsh+1, n
+ do j=1, n2
+ do i=1, n1
+ res(i,j, k) = array(i, j, k-rsh)
+ end do
+ end do
+ end do
+ else
+ stop "Wrong argument to dim"
+ end if
+ end subroutine cshift_sp_3_v1
+end module replacements
+
+program testme
+ use kinds
+ use replacements
+ implicit none
+ integer, parameter :: wp = sp ! Working precision
+ INTEGER, PARAMETER :: n = 7
+ real(kind=wp), dimension(:,:,:), allocatable :: a,b,c
+ integer i, j, k
+ real:: t1, t2
+ integer, parameter :: nrep = 20
+
+ allocate (a(n,n,n), b(n,n,n),c(n,n,n))
+ call random_number(a)
+ do k = 1,3
+ do i=-3,3,2
+ call cshift_sp_3_v1 (a, i, k, b)
+ c = cshift(a,i,k)
+ if (any (c /= b)) call abort
+ end do
+ end do
+ deallocate (b,c)
+ allocate (b(n-1,n-1,n-1),c(n-1,n-1,n-1))
+ do k=1,3
+ do i=-3,3,2
+ call cshift_sp_3_v1 (a(1:n-1,1:n-1,1:n-1), i, k, b)
+ c = cshift(a(1:n-1,1:n-1,1:n-1), i, k)
+ if (any (c /= b)) call abort
+ end do
+ end do
+end program testme
diff --git a/gcc/testsuite/gfortran.dg/cshift_2.f90 b/gcc/testsuite/gfortran.dg/cshift_2.f90
new file mode 100644
index 00000000000..66a6e2b7268
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/cshift_2.f90
@@ -0,0 +1,152 @@
+! { dg-do run }
+! Test CSHIFT with array argument for shift
+module rnd
+ implicit none
+contains
+ subroutine fill(a,n)
+ integer, intent(out), dimension(:,:) :: a
+ integer, intent(in) :: n
+ real, dimension(size(a,1),size(a,2)) :: r
+ call random_number(r)
+ a = int(2*n*r-n)
+ end subroutine fill
+end module rnd
+
+module csh
+ implicit none
+contains
+ subroutine emul_cshift(a,sh_in,dim, c)
+ integer, dimension(:,:,:), intent(in) :: a
+ integer, dimension(:,:,:), intent(out) :: c
+ integer, dimension(:,:), intent(in) :: sh_in
+ integer, intent(in) :: dim
+ integer :: sh, rsh
+ integer :: s1, s2, s3, n, i
+ integer :: n1, n2, n3
+ n1 = size(a,1)
+ n2 = size(a,2)
+ n3 = size(a,3)
+ if (dim == 1) then
+ n = n1
+ do s2=1,n2
+ do s3=1,n3
+ sh = modulo(sh_in(s2,s3), n)
+ rsh = n - sh
+ do i=1,rsh
+ c(i,s2,s3) = a(i+sh,s2,s3)
+ end do
+ do i=rsh+1,n
+ c(i,s2,s3) = a(i-rsh,s2,s3)
+ end do
+ end do
+ end do
+ else if (dim == 2) then
+ n = n2
+ do s3=1,n3
+ do s1=1,n1
+ sh = modulo(sh_in(s1,s3),n)
+ rsh = n - sh
+ do i=1,rsh
+ c(s1,i,s3) = a(s1,i+sh,s3)
+ end do
+ do i=rsh+1,n
+ c(s1,i,s3) = a(s1,i-rsh,s3)
+ end do
+ end do
+ end do
+
+ else if (dim == 3) then
+ n = n3
+ do s2=1,n2
+ do s1=1,n1
+ sh = modulo(sh_in(s1,s2),n)
+ rsh = n - sh
+ do i=1,rsh
+ c(s1,s2,i) = a(s1,s2,i+sh)
+ end do
+ do i=rsh+1,n
+ c(s1,s2,i) = a(s1,s2,i-rsh)
+ end do
+ end do
+ end do
+ else
+ stop "Illegal dim"
+ end if
+ end subroutine emul_cshift
+end module csh
+program main
+ use csh
+ use rnd
+ implicit none
+ integer, parameter :: n1=30,n2=40,n3=50
+ integer, dimension(n1,n2,n3) :: a, b,c
+ integer :: s1, s2, s3
+ integer :: dim
+ integer, dimension(:,:), allocatable :: sh1, sh2, sh3
+ integer, dimension(:), allocatable :: sh_shift
+ integer :: sh, rsh
+ integer :: i,j,k,v
+ type t
+ integer :: i1, i2, i3
+ end type t
+ type(t), dimension(n1,n2,n3) :: ta, tb
+
+ v = 1
+ do k=1,n3
+ do j=1,n2
+ do i=1,n1
+ a(i,j,k) = v
+ v = v + 1
+ end do
+ end do
+ end do
+
+ ta%i1 = a
+ ta%i2 = a+a
+ ta%i3 = a+a+a
+ allocate(sh1(n2,n3))
+ allocate(sh2(n1,n3))
+ allocate(sh3(n1,n2))
+
+ call fill(sh1,10)
+ call fill(sh2,10)
+ call fill(sh3,10)
+
+ b = cshift(a,sh1,1)
+ call emul_cshift(a,sh1,1,c)
+ if (any(b /= c)) then
+ print *,b
+ print *,c
+ call abort
+ end if
+ tb = cshift(ta,sh1,1)
+ if (any(tb%i1 /= c)) call abort
+
+ b = cshift(a,sh2,2)
+ call emul_cshift(a,sh2,2,c)
+ if (any(b /= c)) call abort
+ tb = cshift(ta,sh2,2)
+ if (any (tb%i2 /= c*2)) call abort
+
+ b = cshift(a,sh3,3)
+ call emul_cshift(a,sh3,3,c)
+ if (any(b /= c)) call abort
+ tb = cshift(ta,sh3,3)
+ if (any(tb%i3 /= c*3)) call abort
+
+ b = -42
+ c = -42
+ b(1:n1:2,:,:) = cshift(a(1:n1/2,:,:),sh1,1)
+ call emul_cshift(a(1:n1/2,:,:), sh1, 1, c(1:n1:2,:,:))
+ if (any(b /= c)) call abort
+
+ tb%i1 = -42
+ tb%i2 = -2*42
+ tb%i3 = -3*42
+ tb(1:n1:2,:,:) = cshift(ta(1:n1/2,:,:),sh1,1)
+ if (any(tb%i1 /= b)) call abort
+ if (any(tb%i2 /= 2*b)) call abort
+ if (any(tb%i3 /= 3*b)) call abort
+
+9000 format (99(3(I3,1X),2X))
+end program main
diff --git a/gcc/testsuite/gfortran.dg/debug/pr35154-stabs.f b/gcc/testsuite/gfortran.dg/debug/pr35154-stabs.f
index fd731994f36..99f3e2b7a11 100644
--- a/gcc/testsuite/gfortran.dg/debug/pr35154-stabs.f
+++ b/gcc/testsuite/gfortran.dg/debug/pr35154-stabs.f
@@ -1,6 +1,6 @@
C Test program for common block debugging. G. Helffrich 11 July 2004.
C { dg-do compile }
-C { dg-skip-if "No stabs" { aarch64*-*-* mmix-*-* alpha*-*-* hppa*64*-*-* ia64-*-* *-*-vxworks* } { "*" } { "" } }
+C { dg-skip-if "No stabs" { aarch64*-*-* mmix-*-* alpha*-*-* hppa*64*-*-* ia64-*-* *-*-vxworks* } }
C { dg-skip-if "No stabs" {*-*-* } { "*" } { "-gstabs" } }
common i,j
common /label/l,m
diff --git a/gcc/testsuite/gfortran.dg/fmt_pf.f90 b/gcc/testsuite/gfortran.dg/fmt_pf.f90
index 6cefa86e4a8..743fcbf680b 100644
--- a/gcc/testsuite/gfortran.dg/fmt_pf.f90
+++ b/gcc/testsuite/gfortran.dg/fmt_pf.f90
@@ -223,4 +223,4 @@ contains
end subroutine
end program
-! { dg-output "All kinds rounded to nearest" { xfail { i?86-*-solaris2.9* hppa*-*-hpux* } } }
+! { dg-output "All kinds rounded to nearest" { xfail { hppa*-*-hpux* } } }
diff --git a/gcc/testsuite/gfortran.dg/guality/pr41558.f90 b/gcc/testsuite/gfortran.dg/guality/pr41558.f90
index 840b2384012..34288377334 100644
--- a/gcc/testsuite/gfortran.dg/guality/pr41558.f90
+++ b/gcc/testsuite/gfortran.dg/guality/pr41558.f90
@@ -1,6 +1,6 @@
! PR debug/41558
! { dg-do run }
-! { dg-skip-if "PR testsuite/51875" { { hppa*-*-hpux* } && { ! lp64 } } { "*" } { "" } }
+! { dg-skip-if "PR testsuite/51875" { { hppa*-*-hpux* } && { ! lp64 } } }
! { dg-options "-g" }
subroutine f (s)
diff --git a/gcc/testsuite/gfortran.dg/implicit_class_1.f90 b/gcc/testsuite/gfortran.dg/implicit_class_1.f90
index 380942cfdba..ae689704525 100644
--- a/gcc/testsuite/gfortran.dg/implicit_class_1.f90
+++ b/gcc/testsuite/gfortran.dg/implicit_class_1.f90
@@ -1,5 +1,5 @@
! { dg-do run }
-! { dg-skip-if "" { powerpc-ibm-aix* } { "*" } { "" } }
+! { dg-skip-if "" { powerpc-ibm-aix* } }
!
! PR 56500: [OOP] "IMPLICIT CLASS(...)" wrongly rejected
!
diff --git a/gcc/testsuite/gfortran.dg/init_flag_10.f90 b/gcc/testsuite/gfortran.dg/init_flag_10.f90
index 826a34b81ea..dac9418d614 100644
--- a/gcc/testsuite/gfortran.dg/init_flag_10.f90
+++ b/gcc/testsuite/gfortran.dg/init_flag_10.f90
@@ -1,7 +1,7 @@
! { dg-do run }
! { dg-options "-finit-real=NAN" }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
!
! PR fortran/50619
!
diff --git a/gcc/testsuite/gfortran.dg/init_flag_3.f90 b/gcc/testsuite/gfortran.dg/init_flag_3.f90
index e4426177ab6..30e00814490 100644
--- a/gcc/testsuite/gfortran.dg/init_flag_3.f90
+++ b/gcc/testsuite/gfortran.dg/init_flag_3.f90
@@ -1,7 +1,7 @@
! { dg-do run }
! { dg-options "-finit-integer=-1 -finit-logical=false -finit-real=nan" }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
program init_flag_3
call real_test
diff --git a/gcc/testsuite/gfortran.dg/int_conv_2.f90 b/gcc/testsuite/gfortran.dg/int_conv_2.f90
index ed7a5f4cd60..c6fc00bf1ba 100644
--- a/gcc/testsuite/gfortran.dg/int_conv_2.f90
+++ b/gcc/testsuite/gfortran.dg/int_conv_2.f90
@@ -1,5 +1,5 @@
! { dg-do compile }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
! PR fortran/37930
program test
implicit none
diff --git a/gcc/testsuite/gfortran.dg/isnan_1.f90 b/gcc/testsuite/gfortran.dg/isnan_1.f90
index 89e4cd35ba2..2a13d3a6f93 100644
--- a/gcc/testsuite/gfortran.dg/isnan_1.f90
+++ b/gcc/testsuite/gfortran.dg/isnan_1.f90
@@ -2,7 +2,7 @@
!
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
!
implicit none
real :: x
diff --git a/gcc/testsuite/gfortran.dg/isnan_2.f90 b/gcc/testsuite/gfortran.dg/isnan_2.f90
index 455ecef1f7a..c5360cb0e9f 100644
--- a/gcc/testsuite/gfortran.dg/isnan_2.f90
+++ b/gcc/testsuite/gfortran.dg/isnan_2.f90
@@ -3,7 +3,7 @@
! { dg-do run }
! { dg-options "-fno-range-check" }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
!
implicit none
character(len=1) :: s
diff --git a/gcc/testsuite/gfortran.dg/large_real_kind_2.F90 b/gcc/testsuite/gfortran.dg/large_real_kind_2.F90
index 2e3891b2ffd..7ed4c30e0d5 100644
--- a/gcc/testsuite/gfortran.dg/large_real_kind_2.F90
+++ b/gcc/testsuite/gfortran.dg/large_real_kind_2.F90
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-require-effective-target fortran_large_real }
-! { dg-xfail-if "" { "*-*-freebsd*" } { "*" } { "" } }
+! { dg-xfail-if "" { "*-*-freebsd*" } }
! Testing library calls on large real kinds (larger than kind=8)
implicit none
diff --git a/gcc/testsuite/gfortran.dg/maxloc_2.f90 b/gcc/testsuite/gfortran.dg/maxloc_2.f90
index deca9fc4427..1cf79bace98 100644
--- a/gcc/testsuite/gfortran.dg/maxloc_2.f90
+++ b/gcc/testsuite/gfortran.dg/maxloc_2.f90
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
real :: a(3), nan, minf, pinf
real, allocatable :: c(:)
integer :: ia(1)
diff --git a/gcc/testsuite/gfortran.dg/maxlocval_2.f90 b/gcc/testsuite/gfortran.dg/maxlocval_2.f90
index 5f6b913b0f4..cd985ff4ce9 100644
--- a/gcc/testsuite/gfortran.dg/maxlocval_2.f90
+++ b/gcc/testsuite/gfortran.dg/maxlocval_2.f90
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
real :: a(3), nan, minf, pinf
real, allocatable :: c(:)
logical :: l
diff --git a/gcc/testsuite/gfortran.dg/maxlocval_4.f90 b/gcc/testsuite/gfortran.dg/maxlocval_4.f90
index 029abe3d1a7..b8743325ad8 100644
--- a/gcc/testsuite/gfortran.dg/maxlocval_4.f90
+++ b/gcc/testsuite/gfortran.dg/maxlocval_4.f90
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
real :: a(3,3), b(3), nan, minf, pinf, h
logical :: l, l2
logical :: l3(3,3), l4(3,3), l5(3,3)
diff --git a/gcc/testsuite/gfortran.dg/minloc_1.f90 b/gcc/testsuite/gfortran.dg/minloc_1.f90
index 25691b0682a..b8572945b31 100644
--- a/gcc/testsuite/gfortran.dg/minloc_1.f90
+++ b/gcc/testsuite/gfortran.dg/minloc_1.f90
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
real :: a(3), nan, minf, pinf
integer :: ia(1)
real, allocatable :: c(:)
diff --git a/gcc/testsuite/gfortran.dg/minlocval_1.f90 b/gcc/testsuite/gfortran.dg/minlocval_1.f90
index 261cab346a9..c877f1e823a 100644
--- a/gcc/testsuite/gfortran.dg/minlocval_1.f90
+++ b/gcc/testsuite/gfortran.dg/minlocval_1.f90
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
real :: a(3), nan, minf, pinf
real, allocatable :: c(:)
logical :: l
diff --git a/gcc/testsuite/gfortran.dg/minlocval_4.f90 b/gcc/testsuite/gfortran.dg/minlocval_4.f90
index c42b0194421..b37123164b2 100644
--- a/gcc/testsuite/gfortran.dg/minlocval_4.f90
+++ b/gcc/testsuite/gfortran.dg/minlocval_4.f90
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
real :: a(3,3), b(3), nan, minf, pinf, h
logical :: l, l2
logical :: l3(3,3), l4(3,3), l5(3,3)
diff --git a/gcc/testsuite/gfortran.dg/module_nan.f90 b/gcc/testsuite/gfortran.dg/module_nan.f90
index 5f41514bc0b..7e496c07161 100644
--- a/gcc/testsuite/gfortran.dg/module_nan.f90
+++ b/gcc/testsuite/gfortran.dg/module_nan.f90
@@ -1,7 +1,7 @@
! { dg-do run }
! { dg-options "-fno-range-check" }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
!
! PR fortran/34318
!
diff --git a/gcc/testsuite/gfortran.dg/namelist_42.f90 b/gcc/testsuite/gfortran.dg/namelist_42.f90
index f15914ff117..9875d6ada1d 100644
--- a/gcc/testsuite/gfortran.dg/namelist_42.f90
+++ b/gcc/testsuite/gfortran.dg/namelist_42.f90
@@ -1,6 +1,6 @@
! { dg-do run { target fd_truncate } }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
!
! PR fortran/34427
!
diff --git a/gcc/testsuite/gfortran.dg/namelist_43.f90 b/gcc/testsuite/gfortran.dg/namelist_43.f90
index d2f077e9c48..a6e4eb67885 100644
--- a/gcc/testsuite/gfortran.dg/namelist_43.f90
+++ b/gcc/testsuite/gfortran.dg/namelist_43.f90
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
!
! PR fortran/34427
!
diff --git a/gcc/testsuite/gfortran.dg/nan_1.f90 b/gcc/testsuite/gfortran.dg/nan_1.f90
index 4ff1b873f0c..cfa85059414 100644
--- a/gcc/testsuite/gfortran.dg/nan_1.f90
+++ b/gcc/testsuite/gfortran.dg/nan_1.f90
@@ -3,7 +3,7 @@
!
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
!
module aux2
interface isnan
diff --git a/gcc/testsuite/gfortran.dg/nan_2.f90 b/gcc/testsuite/gfortran.dg/nan_2.f90
index 709b1471830..9077883eb1a 100644
--- a/gcc/testsuite/gfortran.dg/nan_2.f90
+++ b/gcc/testsuite/gfortran.dg/nan_2.f90
@@ -1,7 +1,7 @@
! { dg-do run }
! { dg-options "-fno-range-check -pedantic" }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
!
! PR fortran/34333
!
diff --git a/gcc/testsuite/gfortran.dg/nan_3.f90 b/gcc/testsuite/gfortran.dg/nan_3.f90
index 0a46fdb6ce4..aecb42b68a8 100644
--- a/gcc/testsuite/gfortran.dg/nan_3.f90
+++ b/gcc/testsuite/gfortran.dg/nan_3.f90
@@ -1,7 +1,7 @@
! { dg-do run }
! { dg-options "-fno-range-check" }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
!
! PR fortran/34319
!
diff --git a/gcc/testsuite/gfortran.dg/nan_4.f90 b/gcc/testsuite/gfortran.dg/nan_4.f90
index 30e2a49480d..46aba3ebabd 100644
--- a/gcc/testsuite/gfortran.dg/nan_4.f90
+++ b/gcc/testsuite/gfortran.dg/nan_4.f90
@@ -1,7 +1,7 @@
! { dg-do compile }
! { dg-options "-std=gnu" }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
!
! PR fortran/34398.
!
diff --git a/gcc/testsuite/gfortran.dg/nan_5.f90 b/gcc/testsuite/gfortran.dg/nan_5.f90
index be1169d93d1..af77090d320 100644
--- a/gcc/testsuite/gfortran.dg/nan_5.f90
+++ b/gcc/testsuite/gfortran.dg/nan_5.f90
@@ -4,7 +4,7 @@
!
! { dg-options "-fno-range-check" }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
implicit none
real, parameter :: inf = 2 * huge(inf)
diff --git a/gcc/testsuite/gfortran.dg/nan_6.f90 b/gcc/testsuite/gfortran.dg/nan_6.f90
index 8f0af294420..f4adcd2100d 100644
--- a/gcc/testsuite/gfortran.dg/nan_6.f90
+++ b/gcc/testsuite/gfortran.dg/nan_6.f90
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
!
! List-directed part of PR fortran/43298
! and follow up to PR fortran/34319.
diff --git a/gcc/testsuite/gfortran.dg/nan_7.f90 b/gcc/testsuite/gfortran.dg/nan_7.f90
index 4c2f62eeaed..4aecfd64627 100644
--- a/gcc/testsuite/gfortran.dg/nan_7.f90
+++ b/gcc/testsuite/gfortran.dg/nan_7.f90
@@ -2,7 +2,7 @@
! { dg-options "-fno-range-check" }
! { dg-require-effective-target fortran_real_16 }
! { dg-require-effective-target fortran_integer_16 }
-! { dg-skip-if "" { "powerpc*le-*-*" } { "*" } { "" } }
+! { dg-skip-if "" { "powerpc*le-*-*" } }
! PR47293 NAN not correctly read
character(len=200) :: str
real(16) :: r
diff --git a/gcc/testsuite/gfortran.dg/nearest_1.f90 b/gcc/testsuite/gfortran.dg/nearest_1.f90
index ae9e75f1e8f..1518e867d8a 100644
--- a/gcc/testsuite/gfortran.dg/nearest_1.f90
+++ b/gcc/testsuite/gfortran.dg/nearest_1.f90
@@ -1,7 +1,7 @@
! { dg-do run }
! { dg-options "-O0 -ffloat-store" }
! { dg-add-options ieee }
-! { dg-skip-if "Denormals not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "Denormals not supported" { spu-*-* } }
! PR fortran/27021
! Original code submitted by Dominique d'Humieres
! Converted to Dejagnu for the testsuite by Steven G. Kargl
diff --git a/gcc/testsuite/gfortran.dg/nearest_3.f90 b/gcc/testsuite/gfortran.dg/nearest_3.f90
index 7d683167005..4aa0f4cae82 100644
--- a/gcc/testsuite/gfortran.dg/nearest_3.f90
+++ b/gcc/testsuite/gfortran.dg/nearest_3.f90
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
!
! PR fortran/34209
!
diff --git a/gcc/testsuite/gfortran.dg/pr20257.f90 b/gcc/testsuite/gfortran.dg/pr20257.f90
index aebfc03543f..03108b95183 100644
--- a/gcc/testsuite/gfortran.dg/pr20257.f90
+++ b/gcc/testsuite/gfortran.dg/pr20257.f90
@@ -1,5 +1,5 @@
! { dg-do run }
-! { dg-skip-if "Too big for local store" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "Too big for local store" { spu-*-* } }
integer,parameter :: n = 10000
real(8) array(10000)
diff --git a/gcc/testsuite/gfortran.dg/pr47614.f b/gcc/testsuite/gfortran.dg/pr47614.f
index 52f14c0c17b..2317d72a66e 100644
--- a/gcc/testsuite/gfortran.dg/pr47614.f
+++ b/gcc/testsuite/gfortran.dg/pr47614.f
@@ -1,5 +1,5 @@
! { dg-do run { target { powerpc*-*-* } } }
-! { dg-skip-if "" { powerpc*-*-darwin* } { "*" } { "" } }
+! { dg-skip-if "" { powerpc*-*-darwin* } }
! { dg-options "-O3 -funroll-loops -ffast-math -mcpu=power4" }
diff --git a/gcc/testsuite/gfortran.dg/pr68078.f90 b/gcc/testsuite/gfortran.dg/pr68078.f90
index 092ab29f450..ebe26d55d2b 100644
--- a/gcc/testsuite/gfortran.dg/pr68078.f90
+++ b/gcc/testsuite/gfortran.dg/pr68078.f90
@@ -1,4 +1,4 @@
-! { dg-do run { target x86_64-*-linux* } }
+! { dg-do run { target i?86-*-linux* x86_64-*-linux* } }
! { dg-additional-sources set_vm_limit.c }
!
! This test calls set_vm_limit to set an artificially low address space
diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_51.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_51.f90
new file mode 100644
index 00000000000..cfe9818706f
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_51.f90
@@ -0,0 +1,36 @@
+! { dg-do compile }
+! { dg-options "-fdump-tree-original" }
+!
+! PR 80983: [F03] memory leak when calling procedure-pointer component with allocatable result
+!
+! Contributed by Janus Weil <janus@gcc.gnu.org>
+
+program test
+ implicit none
+
+ type :: concrete_type
+ procedure (alloc_integer), pointer, nopass :: alloc
+ end type
+
+ procedure (alloc_integer), pointer :: pp
+
+ type(concrete_type) :: concrete
+
+ print *, alloc_integer() ! case #1: plain function
+
+ pp => alloc_integer
+ print *, pp() ! case #2: procedure pointer
+
+ concrete % alloc => alloc_integer
+ print *, concrete % alloc() ! case #3: procedure-pointer component
+
+contains
+
+ function alloc_integer() result(res)
+ integer, allocatable :: res
+ allocate(res, source=13)
+ end function
+
+end
+
+! { dg-final { scan-tree-dump-times "__builtin_free" 3 "original" } }
diff --git a/gcc/testsuite/gfortran.dg/read_infnan_1.f90 b/gcc/testsuite/gfortran.dg/read_infnan_1.f90
index c5023e8fe22..7fe2a0ac23e 100644
--- a/gcc/testsuite/gfortran.dg/read_infnan_1.f90
+++ b/gcc/testsuite/gfortran.dg/read_infnan_1.f90
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
! PR43298 Fortran library does not read in NaN, NaN(), -Inf, or Inf
diff --git a/gcc/testsuite/gfortran.dg/real_const_3.f90 b/gcc/testsuite/gfortran.dg/real_const_3.f90
index c70591d3cfc..b214bd0b1a6 100644
--- a/gcc/testsuite/gfortran.dg/real_const_3.f90
+++ b/gcc/testsuite/gfortran.dg/real_const_3.f90
@@ -1,7 +1,7 @@
!{ dg-do run }
!{ dg-options "-fno-range-check" }
!{ dg-add-options ieee }
-!{ dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+!{ dg-skip-if "NaN not supported" { spu-*-* } }
! PR19310 and PR19904, allow disabling range check during compile.
! Contributed by Jerry DeLisle <jvdelisle@gcc.gnu.org>
program main
diff --git a/gcc/testsuite/gfortran.dg/realloc_on_assign_2.f03 b/gcc/testsuite/gfortran.dg/realloc_on_assign_2.f03
index 0564d0d5064..6d6680d984c 100644
--- a/gcc/testsuite/gfortran.dg/realloc_on_assign_2.f03
+++ b/gcc/testsuite/gfortran.dg/realloc_on_assign_2.f03
@@ -1,5 +1,5 @@
! { dg-do run }
-! { dg-skip-if "Too big for local store" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "Too big for local store" { spu-*-* } }
! Tests the patch that implements F2003 automatic allocation and
! reallocation of allocatable arrays on assignment. The tests
! below were generated in the final stages of the development of
diff --git a/gcc/testsuite/gfortran.dg/scratch_1.f90 b/gcc/testsuite/gfortran.dg/scratch_1.f90
index fd888cc9805..a1762fc8c2e 100644
--- a/gcc/testsuite/gfortran.dg/scratch_1.f90
+++ b/gcc/testsuite/gfortran.dg/scratch_1.f90
@@ -1,5 +1,5 @@
! { dg-do run }
-! { dg-skip-if "Too big for local store" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "Too big for local store" { spu-*-* } }
! Check that we can open more than 26 scratch files concurrently
integer :: i
do i = 1, 30
diff --git a/gcc/testsuite/gfortran.dg/stat_1.f90 b/gcc/testsuite/gfortran.dg/stat_1.f90
index ec582f904a5..49ef23a7800 100644
--- a/gcc/testsuite/gfortran.dg/stat_1.f90
+++ b/gcc/testsuite/gfortran.dg/stat_1.f90
@@ -1,5 +1,5 @@
! { dg-do run }
-! { dg-skip-if "" { *-*-mingw* spu-*-* } { "*" } { "" } }
+! { dg-skip-if "" { *-*-mingw* spu-*-* } }
! { dg-options "-std=gnu" }
character(len=*), parameter :: f = "testfile_stat_1"
integer :: s1(13), r1, s2(13), r2, s3(13), r3, d(13), rd
diff --git a/gcc/testsuite/gfortran.dg/stat_2.f90 b/gcc/testsuite/gfortran.dg/stat_2.f90
index a3eb6b2d475..ae029dc9424 100644
--- a/gcc/testsuite/gfortran.dg/stat_2.f90
+++ b/gcc/testsuite/gfortran.dg/stat_2.f90
@@ -1,5 +1,5 @@
! { dg-do run }
-! { dg-skip-if "" { *-*-mingw* spu-*-* } { "*" } { "" } }
+! { dg-skip-if "" { *-*-mingw* spu-*-* } }
! { dg-options "-std=gnu" }
character(len=*), parameter :: f = "testfile_stat_2"
integer :: s1(13), r1, s2(13), r2, s3(13), r3, d(13), rd
diff --git a/gcc/testsuite/gfortran.dg/transfer_simplify_1.f90 b/gcc/testsuite/gfortran.dg/transfer_simplify_1.f90
index 4f92121a572..8a3340aae90 100644
--- a/gcc/testsuite/gfortran.dg/transfer_simplify_1.f90
+++ b/gcc/testsuite/gfortran.dg/transfer_simplify_1.f90
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-options "-O2" }
-! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "NaN not supported" { spu-*-* } }
! Tests that the PRs caused by the lack of gfc_simplify_transfer are
! now fixed. These were brought together in the meta-bug PR31237
! (TRANSFER intrinsic).
diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_9.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_9.f03
index 6e625262c31..e4c6b6e4e5b 100644
--- a/gcc/testsuite/gfortran.dg/typebound_operator_9.f03
+++ b/gcc/testsuite/gfortran.dg/typebound_operator_9.f03
@@ -1,6 +1,6 @@
! { dg-do run }
! { dg-add-options ieee }
-! { dg-skip-if "Too big for local store" { spu-*-* } { "*" } { "" } }
+! { dg-skip-if "Too big for local store" { spu-*-* } }
!
! Solve a diffusion problem using an object-oriented approach
!
diff --git a/gcc/testsuite/gfortran.dg/vect/fast-math-pr38968.f90 b/gcc/testsuite/gfortran.dg/vect/fast-math-pr38968.f90
index c34a077e430..f5bc41a573b 100644
--- a/gcc/testsuite/gfortran.dg/vect/fast-math-pr38968.f90
+++ b/gcc/testsuite/gfortran.dg/vect/fast-math-pr38968.f90
@@ -1,7 +1,7 @@
! Skip this on platforms that don't have the vectorization instructions
! to handle complex types. This test is very slow on these platforms so
! skipping is better then running it unvectorized.
-! { dg-skip-if "" { ia64-*-* sparc*-*-* } { "*" } { "" } }
+! { dg-skip-if "" { ia64-*-* sparc*-*-* } }
! It can be slow on some x86 CPUs.
! { dg-timeout-factor 2 }
program mymatmul