OSDN Git Service

* config/i386/i386.md (UNSPEC_VSIBADDR): New.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / intent_out_2.f90
1 ! { dg-do run }
2 ! Tests the fix for PR33554, in which the default initialization
3 ! of temp, in construct_temp, caused a segfault because it was
4 ! being done before the array offset and lower bound were
5 ! available.
6 !
7 ! Contributed by Harald Anlauf <anlauf@gmx.de> 
8 !
9 module gfcbug72
10   implicit none
11
12   type t_datum
13     character(len=8) :: mn = 'abcdefgh'
14   end type t_datum
15
16   type t_temp
17     type(t_datum) :: p
18   end type t_temp
19
20 contains
21
22   subroutine setup ()
23     integer :: i
24     type (t_temp), pointer :: temp(:) => NULL ()
25
26     do i=1,2
27        allocate (temp (2))
28        call construct_temp (temp)
29        if (any (temp % p% mn .ne. 'ijklmnop')) call abort ()
30        deallocate (temp)
31     end do
32   end subroutine setup
33   !--
34   subroutine construct_temp (temp)
35     type (t_temp), intent(out) :: temp (:)
36     if (any (temp % p% mn .ne. 'abcdefgh')) call abort ()
37     temp(:)% p% mn = 'ijklmnop'
38   end subroutine construct_temp
39 end module gfcbug72
40
41 program test
42   use gfcbug72
43   implicit none
44   call setup ()
45 end program test
46 ! { dg-final { cleanup-modules "gfcbug72" } }
47