2018-09-30 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / alloc_comp_default_init_2.f90
blobd9a386676d7562f80b5cc139fea5afad3f5a68f6
1 ! { dg-do run }
2 ! Tests the fix for PR35959, in which the structure subpattern was declared static
3 ! so that this test faied on the second recursive call.
5 ! Contributed by Michaƫl Baudin <michael.baudin@gmail.com>
7 program testprog
8 type :: t_type
9 integer, dimension(:), allocatable :: chars
10 end type t_type
11 integer, save :: callnb = 0
12 type(t_type) :: this
13 allocate ( this % chars ( 4))
14 if (.not.recursivefunc (this) .or. (callnb .ne. 10)) STOP 1
15 contains
16 recursive function recursivefunc ( this ) result ( match )
17 type(t_type), intent(in) :: this
18 type(t_type) :: subpattern
19 logical :: match
20 callnb = callnb + 1
21 match = (callnb == 10)
22 if ((.NOT. allocated (this % chars)) .OR. match) return
23 allocate ( subpattern % chars ( 4 ) )
24 match = recursivefunc ( subpattern )
25 end function recursivefunc
26 end program testprog