OSDN Git Service

Fix PR42186.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / alloc_comp_assign_7.f90
1 ! { dg-do run }
2 !
3 ! Test the fix for PR37735, in which gfc gagged in the assignement to
4 ! 'p'.  The array component 'r' caused an ICE.
5 !
6 ! Contributed by Steven Winfield <saw44@cam.ac.uk>
7 !
8 module PrettyPix_module
9   implicit none
10   type Spline
11      real, allocatable, dimension(:) ::y2
12   end type Spline
13   type Path
14      type(Spline) :: r(3)
15   end type Path
16   type Scene
17      type(path) :: look_at_path
18   end type Scene
19 contains
20   subroutine scene_set_look_at_path(this,p)
21     type(scene), intent(inout) :: this
22     type(path),  intent(in)    :: p
23     this%look_at_path = p
24   end subroutine scene_set_look_at_path
25 end module PrettyPix_module
26
27   use PrettyPix_module
28   implicit none
29   integer :: i
30   real :: x(3) = [1.0, 2.0, 3.0]
31   type(scene) :: this
32   type(path)  :: p
33   p = path ([spline([x(1)]),spline([x(2)]),spline([x(3)])])
34   call scene_set_look_at_path(this,p)
35   do i = 1, 3
36     if (this%look_at_path%r(i)%y2(1) .ne. x(i)) call abort
37   end do
38 end
39
40 ! { dg-final { cleanup-modules "PrettyPix_module" } }