re PR fortran/78741 (ICE in gfc_get_symbol_decl, at fortran/trans-decl.c:1534)
[official-gcc.git] / gcc / testsuite / gfortran.dg / pdt_2.f03
blob34e217dc787308ab90f2e1071c7760264c9d317d
1 ! { dg-do run }
2 ! { dg-options "-fcheck=all" }
3 ! { dg-shouldfail "value of the PDT LEN parameter" }
5 ! Reduced version of pdt_1.f03 to check that an incorrect
6 ! value for the parameter 'b' in the dummy is picked up.
8   implicit none
9   integer, parameter :: ftype = kind(0.0e0)
10   integer :: i
11   type :: mytype (a,b)
12     integer, kind :: a = kind(0.0d0)
13     integer, LEN :: b
14     integer :: i
15     real(kind = a) :: d(b, b)
16     character (len = b*b) :: chr
17   end type
19   type(mytype(ftype, 4)) :: z2
20   call foobar (z2)
21 contains
22   subroutine foobar (arg)
23     type(mytype(ftype, 8)) :: arg
24     print *, arg%i
25   end subroutine
26 end