[WebAssembly] Fix asan issue from https://reviews.llvm.org/D121349
[llvm-project.git] / flang / test / Semantics / structconst01.f90
blob7df6cfc4231efc56a1517266096c3c54d5b52a04
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Error tests for structure constructors.
3 ! Errors caught by name resolution are tested elsewhere; these are the
4 ! errors meant to be caught by expression semantic analysis, as well as
5 ! acceptable use cases.
6 ! Type parameters are used here to make the parses unambiguous.
7 ! C796 (R756) The derived-type-spec shall not specify an abstract type (7.5.7).
8 ! This refers to a derived-type-spec used in a structure constructor
10 module module1
11 type :: type1(j)
12 integer, kind :: j
13 integer :: n = 1
14 end type type1
15 type, extends(type1) :: type2(k)
16 integer, kind :: k
17 integer :: m
18 end type type2
19 type, abstract :: abstract(j)
20 integer, kind :: j
21 integer :: n
22 end type abstract
23 type :: privaten(j)
24 integer, kind :: j
25 integer, private :: n
26 end type privaten
27 contains
28 subroutine type1arg(x)
29 type(type1(0)), intent(in) :: x
30 end subroutine type1arg
31 subroutine type2arg(x)
32 type(type2(0,0)), intent(in) :: x
33 end subroutine type2arg
34 subroutine abstractarg(x)
35 class(abstract(0)), intent(in) :: x
36 end subroutine abstractarg
37 subroutine errors
38 call type1arg(type1(0)())
39 call type1arg(type1(0)(1))
40 call type1arg(type1(0)(n=1))
41 !ERROR: Type parameter 'j' may not appear as a component of a structure constructor
42 call type1arg(type1(0)(j=1))
43 !ERROR: Component 'n' conflicts with another component earlier in this structure constructor
44 call type1arg(type1(0)(1,n=2))
45 !ERROR: Value in structure constructor lacks a component name
46 call type1arg(type1(0)(n=1,2))
47 !ERROR: Component 'n' conflicts with another component earlier in this structure constructor
48 call type1arg(type1(0)(n=1,n=2))
49 !ERROR: Unexpected value in structure constructor
50 call type1arg(type1(0)(1,2))
51 call type2arg(type2(0,0)(n=1,m=2))
52 call type2arg(type2(0,0)(m=2))
53 !ERROR: Structure constructor lacks a value for component 'm'
54 call type2arg(type2(0,0)())
55 call type2arg(type2(0,0)(type1=type1(0)(n=1),m=2))
56 call type2arg(type2(0,0)(type1=type1(0)(),m=2))
57 !ERROR: Component 'type1' conflicts with another component earlier in this structure constructor
58 call type2arg(type2(0,0)(n=1,type1=type1(0)(n=2),m=3))
59 !ERROR: Component 'n' conflicts with another component earlier in this structure constructor
60 call type2arg(type2(0,0)(type1=type1(0)(n=1),n=2,m=3))
61 !ERROR: Component 'n' conflicts with another component earlier in this structure constructor
62 call type2arg(type2(0,0)(type1=type1(0)(1),n=2,m=3))
63 !ERROR: Type parameter 'j' may not appear as a component of a structure constructor
64 call type2arg(type2(0,0)(j=1, &
65 !ERROR: Type parameter 'k' may not appear as a component of a structure constructor
66 k=2,m=3))
67 !ERROR: ABSTRACT derived type 'abstract' may not be used in a structure constructor
68 call abstractarg(abstract(0)(n=1))
69 !This case is ok
70 end subroutine errors
71 subroutine polycomponent
72 type :: poly
73 class(*), allocatable :: p
74 end type poly
75 type(poly) :: x
76 type :: poly2
77 class(type1(1)), allocatable :: p1
78 type(type1(1)), allocatable :: p2
79 end type poly2
80 type(type1(1)) :: t1val
81 type(poly2) :: x2
82 ! These cases are not errors
83 x = poly(1)
84 x = poly('hello')
85 x = poly(type1(1)(123))
86 x2 = poly2(t1val, t1val)
87 !ERROR: Value in structure constructor is incompatible with component 'p' of type CLASS(*)
88 x = poly(z'feedface')
89 end subroutine
90 end module module1