aboutsummaryrefslogtreecommitdiff
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/gomp/pr71704.f9058
-rw-r--r--gcc/testsuite/gfortran.dg/gomp/pr71705.f907
-rw-r--r--gcc/testsuite/gfortran.dg/gomp/pr71758.f9010
-rw-r--r--gcc/testsuite/gfortran.dg/list_read_14.f9025
-rw-r--r--gcc/testsuite/gfortran.dg/pr70931.f9010
-rw-r--r--gcc/testsuite/gfortran.dg/pr71688.f9013
-rw-r--r--gcc/testsuite/gfortran.dg/pr71764.f9034
-rw-r--r--gcc/testsuite/gfortran.dg/select_type_35.f0341
-rw-r--r--gcc/testsuite/gfortran.dg/unexpected_eof.f8
9 files changed, 206 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/gomp/pr71704.f90 b/gcc/testsuite/gfortran.dg/gomp/pr71704.f90
new file mode 100644
index 00000000000..5c1c003ca57
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/gomp/pr71704.f90
@@ -0,0 +1,58 @@
+! PR fortran/71704
+! { dg-do compile }
+
+real function f0 ()
+!$omp declare simd (f0)
+ f0 = 1
+end
+
+real function f1 ()
+!$omp declare target (f1)
+ f1 = 1
+end
+
+real function f2 ()
+!$omp declare reduction (foo : integer : omp_out = omp_out + omp_in) &
+!$omp & initializer (omp_priv = 0)
+ f2 = 1
+end
+
+real function f3 ()
+ real, save :: t
+!$omp threadprivate (t)
+ f3 = 1
+end
+
+real function f4 ()
+!$omp taskwait
+ f4 = 1
+end
+
+real function f5 ()
+!$omp barrier
+ f5 = 1
+end
+
+real function f6 ()
+!$omp parallel
+!$omp end parallel
+ f6 = 1
+end
+
+real function f7 ()
+!$omp single
+!$omp end single
+ f7 = 1
+end
+
+real function f8 ()
+!$omp critical
+!$omp end critical
+ f8 = 1
+end
+
+real function f9 ()
+!$omp critical
+!$omp end critical
+ f9 = 1
+end
diff --git a/gcc/testsuite/gfortran.dg/gomp/pr71705.f90 b/gcc/testsuite/gfortran.dg/gomp/pr71705.f90
new file mode 100644
index 00000000000..4813aacfdc3
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/gomp/pr71705.f90
@@ -0,0 +1,7 @@
+! PR fortran/71705
+! { dg-do compile }
+
+ real :: x
+ x = 0.0
+ !$omp target update to(x)
+end
diff --git a/gcc/testsuite/gfortran.dg/gomp/pr71758.f90 b/gcc/testsuite/gfortran.dg/gomp/pr71758.f90
new file mode 100644
index 00000000000..47215ba5cd9
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/gomp/pr71758.f90
@@ -0,0 +1,10 @@
+! PR middle-end/71758
+
+subroutine pr71758 (p)
+ integer(8) :: i
+ integer :: p(20)
+ i = 0
+ !$omp target device(i)
+ !$omp end target
+ !$omp target update to(p(1:1)) device(i)
+end subroutine
diff --git a/gcc/testsuite/gfortran.dg/list_read_14.f90 b/gcc/testsuite/gfortran.dg/list_read_14.f90
new file mode 100644
index 00000000000..15bcfad500d
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/list_read_14.f90
@@ -0,0 +1,25 @@
+! { dg-do run }
+! PR70684 incorrect reading of values from file on Windows
+program test
+implicit none
+integer,parameter :: isize=12
+integer,parameter :: funit=12
+integer :: i
+character(1), parameter :: cr=char(13)
+double precision, dimension(isize) :: a, res
+res= (/ 1.0000000000000000, 2.0000000000000000, 3.0000000000000000, &
+ 4.0000000000000000, 5.0000000000000000, 6.0000000000000000, &
+ 7.0000000000000000, 8.0000000000000000, 9.0000000000000000, &
+ 10.000000000000000, 11.000000000000000, 12.000000000000000 /)
+do i=1,isize
+ a(i)=dble(i)
+enddo
+open(funit,status="scratch")
+write(funit,'(1x,6(f25.20,'',''),a)') (a(i),i=1,6), cr
+write(funit,'(1x,6(f25.20,'',''),a)') (a(i),i=7,12), cr
+rewind(funit)
+a=0d0
+read(funit,*) (a(i),i=1,isize)
+close(funit)
+if (any(a /= res)) call abort
+end
diff --git a/gcc/testsuite/gfortran.dg/pr70931.f90 b/gcc/testsuite/gfortran.dg/pr70931.f90
new file mode 100644
index 00000000000..08ecd687752
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr70931.f90
@@ -0,0 +1,10 @@
+! { dg-do compile }
+! { dg-options "-g" }
+program p
+ type t
+ integer :: a
+ integer :: b(0)
+ end type
+ type(t), parameter :: z = t(1, [2])
+ print *, z
+end
diff --git a/gcc/testsuite/gfortran.dg/pr71688.f90 b/gcc/testsuite/gfortran.dg/pr71688.f90
new file mode 100644
index 00000000000..dbb6d185cf4
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr71688.f90
@@ -0,0 +1,13 @@
+! { dg-do compile }
+! { dg-options "-fcoarray=lib" }
+
+program p
+ call s
+contains
+ subroutine s
+ real :: x[*] = 1
+ block
+ end block
+ x = 2
+ end
+end
diff --git a/gcc/testsuite/gfortran.dg/pr71764.f90 b/gcc/testsuite/gfortran.dg/pr71764.f90
new file mode 100644
index 00000000000..48176f8297e
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr71764.f90
@@ -0,0 +1,34 @@
+! { dg-do run }
+! PR71764
+program p
+ use iso_c_binding, only: c_ptr, c_null_ptr, c_ptr, c_associated, c_loc
+ logical, target :: rls
+ real, target :: t = 3.14
+ type(c_ptr) :: nullptr,c
+ real, pointer :: k
+ nullptr = c_null_ptr
+ c = nullptr
+ rls = c_associated(c)
+ if (rls) call abort
+ if (c_associated(c)) call abort
+ c = c_loc(rls)
+ if (.not. c_associated(c)) call abort
+ c = nullptr
+ if (c_associated(c)) call abort
+ c = c_loc(t)
+ k => t
+ call association_test(k, c)
+contains
+ subroutine association_test(a,b)
+ use iso_c_binding, only: c_associated, c_loc, c_ptr
+ implicit none
+ real, pointer :: a
+ type(c_ptr) :: b
+ if(c_associated(b, c_loc(a))) then
+ return
+ else
+ call abort
+ end if
+ end subroutine association_test
+end
+
diff --git a/gcc/testsuite/gfortran.dg/select_type_35.f03 b/gcc/testsuite/gfortran.dg/select_type_35.f03
new file mode 100644
index 00000000000..92d2f275313
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/select_type_35.f03
@@ -0,0 +1,41 @@
+! { dg-do run }
+!
+! Contributed by Nathanael Huebbe
+! Check fix for PR/70842
+
+program foo
+
+ TYPE, ABSTRACT :: t_Intermediate
+ END TYPE t_Intermediate
+
+ type, extends(t_Intermediate) :: t_Foo
+ character(:), allocatable :: string
+ end type t_Foo
+
+ class(t_Foo), allocatable :: obj
+
+ allocate(obj)
+ obj%string = "blabarfoo"
+
+ call bar(obj)
+
+ deallocate(obj)
+contains
+ subroutine bar(me)
+ class(t_Intermediate), target :: me
+
+ class(*), pointer :: alias
+
+ select type(me)
+ type is(t_Foo)
+ if (len(me%string) /= 9) call abort()
+ end select
+
+ alias => me
+ select type(alias)
+ type is(t_Foo)
+ if (len(alias%string) /= 9) call abort()
+ end select
+ end subroutine bar
+end program foo
+
diff --git a/gcc/testsuite/gfortran.dg/unexpected_eof.f b/gcc/testsuite/gfortran.dg/unexpected_eof.f
new file mode 100644
index 00000000000..d3cdb99596a
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/unexpected_eof.f
@@ -0,0 +1,8 @@
+! { dg-do compile }
+! PR66461 ICE on missing end program in fixed source
+ program p
+ integer x(2)
+ x = -1
+ if ( x(1) < 0 .or.
+ & x(2) < 0 ) print *, x
+! { dg-error "Unexpected end of file" "" { target *-*-* } 0 }