xref: /llvm-project/flang/test/Semantics/separate-mp06.f90 (revision c2f642d90d33a4e6c987b52e22eca4221c86c601)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2! Structural equivalence of derived type definitions
3module m
4  interface
5    module subroutine s1(x)
6      type :: nonseq
7        integer :: n
8      end type
9      type(nonseq), intent(in) :: x
10    end subroutine
11    module subroutine s2(x)
12      type :: seq
13        sequence
14        integer :: n
15      end type
16      type(seq), intent(in) :: x
17    end subroutine
18    module subroutine s3(x)
19      type :: chlen
20        sequence
21        character(2) :: s
22      end type
23      type(chlen), intent(in) :: x
24    end subroutine
25    module subroutine s4(x)
26      !ERROR: A sequence type may not have type parameters
27      type :: pdt(k)
28        integer, kind :: k
29        sequence
30        real(k) :: a
31      end type
32      type(pdt(4)), intent(in) :: x
33    end subroutine
34  end interface
35end module
36
37submodule(m) sm
38 contains
39  module subroutine s1(x)
40    type :: nonseq
41      integer :: n
42    end type
43    !ERROR: Dummy argument 'x' has type nonseq; the corresponding argument in the interface body has distinct type nonseq
44    type(nonseq), intent(in) :: x
45  end subroutine
46  module subroutine s2(x) ! ok
47    type :: seq
48      sequence
49      integer :: n
50    end type
51    type(seq), intent(in) :: x
52  end subroutine
53  module subroutine s3(x)
54    type :: chlen
55      sequence
56      character(3) :: s ! note: length is 3, not 2
57    end type
58    !ERROR: Dummy argument 'x' has type chlen; the corresponding argument in the interface body has distinct type chlen
59    type(chlen), intent(in) :: x
60  end subroutine
61  module subroutine s4(x)
62    !ERROR: A sequence type may not have type parameters
63    type :: pdt(k)
64      integer, kind :: k
65      sequence
66      real(k) :: a
67    end type
68    !ERROR: Dummy argument 'x' has type pdt(k=4_4); the corresponding argument in the interface body has distinct type pdt(k=4_4)
69    type(pdt(4)), intent(in) :: x
70  end subroutine
71end submodule
72
73program main
74  use m
75  type :: nonseq
76    integer :: n
77  end type
78  type :: seq
79    sequence
80    integer :: n
81  end type
82  type :: chlen
83    sequence
84    character(2) :: s
85  end type
86  !ERROR: A sequence type may not have type parameters
87  type :: pdt(k)
88    integer, kind :: k
89    sequence
90    real(k) :: a
91  end type
92  !ERROR: Actual argument type 'nonseq' is not compatible with dummy argument type 'nonseq'
93  call s1(nonseq(1))
94  call s2(seq(1)) ! ok
95  call s3(chlen('ab')) ! ok, matches interface
96  !ERROR: Actual argument type 'pdt(k=4_4)' is not compatible with dummy argument type 'pdt(k=4_4)'
97  call s4(pdt(4)(3.14159))
98end program
99