blob: 385eb2715f68e522d6083195ef354f70616cd0b5 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
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
|