1! RUN: %S/test_errors.sh %s %t %f18
2! Error tests for structure constructors.
3! Errors caught by expression resolution are tested elsewhere; these are the
4! errors meant to be caught by name resolution, as well as acceptable use
5! cases.
6! Type parameters are used to make the parses unambiguous.
7
8module module1
9  type :: type1(j)
10    integer, kind :: j
11    integer :: n = 1
12  end type type1
13  type, extends(type1) :: type2(k)
14    integer, kind :: k
15    integer :: m
16  end type type2
17  type :: privaten(j)
18    integer, kind :: j
19    integer, private :: n
20  end type privaten
21 contains
22  subroutine type1arg(x)
23    type(type1(0)), intent(in) :: x
24  end subroutine type1arg
25  subroutine type2arg(x)
26    type(type2(0,0)), intent(in) :: x
27  end subroutine type2arg
28  subroutine errors
29    call type1arg(type1(0)())
30    call type1arg(type1(0)(1))
31    call type1arg(type1(0)(n=1))
32    !ERROR: Keyword 'bad=' does not name a component of derived type 'type1'
33    call type1arg(type1(0)(bad=1))
34    call type2arg(type2(0,0)(n=1,m=2))
35    call type2arg(type2(0,0)(m=2))
36    call type2arg(type2(0,0)(type1=type1(0)(n=1),m=2))
37    call type2arg(type2(0,0)(type1=type1(0)(),m=2))
38  end subroutine errors
39end module module1
40
41module module2
42  !ERROR: No definition found for type parameter 'k'
43  type :: type1(k)
44  end type
45  type(type1):: x
46end module
47