OSDN Git Service

* obj-c++.dg/comp-types-10.mm: XFAIL for ICE.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / used_types_3.f90
1 ! { dg-do compile }
2 ! Test the fix for PR28601 in which line 55 would produce an ICE
3 ! because the rhs and lhs derived times were not identically
4 ! associated and so could not be cast.
5 !
6 ! Contributed by Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
7 !
8 module modA
9 implicit none
10 save
11 private
12
13 type, public :: typA
14 integer :: i
15 end type typA
16
17 type, public :: atom
18 type(typA), pointer :: ofTypA(:,:)
19 end type atom
20 end module modA
21
22 !!! re-name and re-export typA as typB:
23 module modB
24 use modA, only: typB => typA
25 implicit none
26 save
27 private
28
29 public typB
30 end module modB
31
32 !!! mixed used of typA and typeB:
33 module modC
34 use modB
35 implicit none
36 save
37 private
38 contains
39
40 subroutine buggy(a)
41 use modA, only: atom
42 ! use modB, only: typB
43 ! use modA, only: typA
44 implicit none
45 type(atom),intent(inout) :: a
46 target :: a
47 ! *** end of interface ***
48
49 type(typB), pointer :: ofTypB(:,:)
50 ! type(typA), pointer :: ofTypB(:,:)
51 integer :: i,j,k
52
53 ofTypB => a%ofTypA
54
55 a%ofTypA(i,j) = ofTypB(k,j)
56 end subroutine buggy
57 end module modC
58 ! { dg-final { cleanup-modules "modA modB modC" } }