2016-10-23 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / select_type_36.f03
bloba667ece3326063b4b16c0894f88accbb76f77df2
1 ! { dg-do run }
3 ! Test the fix for PR69834 in which the two derived types below
4 ! had the same hash value and so generated an error in the resolution
5 ! of SELECT TYPE.
7 ! Reported by James van Buskirk on clf:
8 ! https://groups.google.com/forum/#!topic/comp.lang.fortran/0bm3E5xJpkM
10 module types
11    implicit none
12    type CS5SS
13       integer x
14       real y
15    end type CS5SS
16    type SQS3C
17       logical u
18       character(7) v
19    end type SQS3C
20    contains
21       subroutine sub(x, switch)
22          class(*), allocatable :: x
23          integer :: switch
24          select type(x)
25             type is(CS5SS)
26                if (switch .ne. 1) call abort
27             type is(SQS3C)
28                if (switch .ne. 2) call abort
29             class default
30                call abort
31          end select
32       end subroutine sub
33 end module types
35 program test
36    use types
37    implicit none
38    class(*), allocatable :: u1, u2
40    allocate(u1,source = CS5SS(2,1.414))
41    allocate(u2,source = SQS3C(.TRUE.,'Message'))
42    call sub(u1, 1)
43    call sub(u2, 2)
44 end program test