diff options
Diffstat (limited to 'gcc/testsuite/gfortran.dg/assign_func_dtcomp_1.f90')
-rw-r--r-- | gcc/testsuite/gfortran.dg/assign_func_dtcomp_1.f90 | 47 |
1 files changed, 47 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/assign_func_dtcomp_1.f90 b/gcc/testsuite/gfortran.dg/assign_func_dtcomp_1.f90 new file mode 100644 index 000000000..385eb2715 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/assign_func_dtcomp_1.f90 @@ -0,0 +1,47 @@ +! { dg-do run } +! { dg-options "-O0" } +! +! Test fix for PR18022. +! +! Contributed by Paul Thomas <pault@gcc.gnu.org> +! +program assign_func_dtcomp + implicit none + type :: mytype + real :: x + real :: y + end type mytype + type (mytype), dimension (4) :: z + + type :: thytype + real :: x(4) + end type thytype + type (thytype) :: w + real, dimension (4) :: a = (/1.,2.,3.,4./) + real, dimension (4) :: b = (/5.,6.,7.,8./) + + +! Test the original problem is fixed. + z(:)%x = foo (a) + z(:)%y = foo (b) + + + if (any(z%x.ne.a).or.any(z%y.ne.b)) call abort () + +! Make sure we did not break anything on the way. + w%x(:) = foo (b) + a = foo (b) + + if (any(w%x.ne.b).or.any(a.ne.b)) call abort () + +contains + + function foo (v) result (ans) + real, dimension (:), intent(in) :: v + real, dimension (size(v)) :: ans + ans = v + end function foo + + +end program assign_func_dtcomp + |