Daily bump.
[official-gcc.git] / gcc / testsuite / gfortran.dg / pdt_25.f03
blob69dfdeb26e3db63d6aa135e76e4f4cb7a99206ec
1 ! {dg-do run }
3 ! Tests the fix for PR82978 in which all the parameterized string
4 ! lengths with the same value of parameter 'k' had the same value
5 ! regardless of the value of 'l'. In this testcase, the length for
6 ! 'l' = 5 was taken.
8 ! Contributed by Fritz Reese  <foreese@gcc.gnu.org>
10   implicit none
12   type :: pdt_t(k, l)
13     integer, kind :: k
14     integer, len :: l
15     character(kind=k,len=l) :: chr
16     integer :: i(l)
17   end type
19   type(pdt_t(1, 4))   :: x1
20   type(pdt_t(1, 5))   :: x2
21   type(pdt_t(4, 5))   :: x3
23   call test (x1, 4)
24   call test (x2, 5)
26 ! Kind tests appear because of problem identified in comment #!
27 ! due to Dominque d'Humieres  <dominiq@lps.ens.fr>
29   if (kind (x2%chr) .ne. 1) call abort
30   if (kind (x3%chr) .ne. 4) call abort
32 contains
34   subroutine test (x, i)
35     type(pdt_t(1, *)) :: x
36     integer :: i
38     if (x%l .ne. i) call abort
39     if (len(x%chr) .ne. i) call abort
40     if (size(x%i,1) .ne. i) call abort
41   end subroutine
43 end