PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / used_dummy_types_4.f90
blob9a627b82ccf4e3673556f7bd6cebcda982b6a495
1 ! { dg-do compile }
2 ! This checks the fix for PR19362 in which types from different scopes
3 ! that are the same, according to 4.4.2, would generate an ICE if one
4 ! were assigned to the other. As well as the test itself, various
5 ! other requirements of 4.4.2 are tested here.
7 ! Contributed by Paul Thomas <pault@gcc.gnu.org>
8 !==============
9 module global
11 TYPE :: seq_type1
12 sequence
13 integer :: i
14 end type seq_type1
16 TYPE :: nonseq_type1
17 integer :: i
18 end type nonseq_type1
19 type (nonseq_type1) :: ns1
21 end module global
23 ! Host types with local name != true name
24 use global, only: seq_type2=>seq_type1, nonseq_type2=>nonseq_type1, ns1
25 type (nonseq_type2) :: ns2
27 ! Host non-sequence types
28 type :: different_type
29 integer :: i
30 end type different_type
31 type (different_type) :: dt1
33 type :: same_type
34 integer :: i
35 end type same_type
36 type (same_type) :: st1
38 real :: seq_type1
40 ! Provide a reference to dt1.
41 dt1 = different_type (42)
42 ! These share a type declaration.
43 ns2 = ns1
44 ! USE associated seq_type1 is renamed.
45 seq_type1 = 1.0
47 ! These are different.
48 st1 = dt ! { dg-error "convert REAL" }
50 call foo (st1) ! { dg-error "Type mismatch in argument" }
52 contains
54 subroutine foo (st2)
56 ! Contained type with local name != true name.
57 ! This is the same as seq_type2 in the host.
58 use global, only: seq_type3=>seq_type1
60 ! This local declaration is the same as seq_type3 and seq_type2.
61 TYPE :: seq_type1
62 sequence
63 integer :: i
64 end type seq_type1
66 ! Host association of renamed type.
67 type (seq_type2) :: x
68 ! Locally declared version of the same thing.
69 type (seq_type1) :: y
70 ! USE associated renamed type.
71 type (seq_type3) :: z
73 ! Contained type that is different to that in the host.
74 type :: different_type
75 complex :: z
76 end type different_type
78 type :: same_type
79 integer :: i
80 end type same_type
82 type (different_type) :: b
83 type (same_type) :: st2
85 ! Error because these are not the same.
86 b = dt1 ! { dg-error "convert TYPE" }
88 ! Error in spite of the name - these are non-sequence types and are NOT
89 ! the same.
90 st1 = st2 ! { dg-error "convert TYPE" }
92 b%z = (2.0,-1.0)
94 ! Check that the references that are correct actually work. These test the
95 ! fix for PR19362.
96 x = seq_type1 (1)
97 y = x
98 y = seq_type3 (99)
99 end subroutine foo