PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / select_type_33.f03
blob3ba27e0103c70910ca1edcedcb7c8546abe1eef2
1 ! { dg-do compile }
3 ! PR fortran/56816
4 ! The unfinished SELECT TYPE statement below was leading to an ICE because
5 ! at the time the statement was rejected, the compiler tried to free
6 ! some symbols that had already been freed with the SELECT TYPE
7 ! namespace.
9 ! Original testcase from Dominique Pelletier <dominique.pelletier@polymtl.ca>
11 module any_list_module
12     implicit none
14     private
15     public :: anylist, anyitem
17     type anylist
18     end type
20     type anyitem
21         class(*), allocatable :: value
22     end type
23 end module any_list_module
26 module my_item_list_module
28     use any_list_module
29     implicit none
31     type, extends (anyitem) :: myitem
32     end type myitem
34 contains
36     subroutine myprint (this)
37         class (myitem) ::   this
39         select type ( v => this % value ! { dg-error "parse error in SELECT TYPE" }
40         end select                      ! { dg-error "Expecting END SUBROUTINE" }
41     end subroutine myprint
43 end module my_item_list_module