1! { dg-do compile }
2!
3! PR 42335: [OOP] ICE on CLASS IS (bad_identifier)
4!
5! Contributed by Harald Anlauf <anlauf@gmx.de>
6
7  implicit none
8  type, abstract :: vector_class
9  end type vector_class
10
11  type, extends(vector_class) :: trivial_vector_type
12    real :: elements(100)
13  end type trivial_vector_type
14
15contains
16
17  subroutine bar (this,v)
18    class(trivial_vector_type), intent(inout) :: this
19    class(vector_class),        intent(in)    :: v
20
21    select type (v)
22    class is (bad_id)                    ! { dg-error " error in CLASS IS specification" }
23       this%elements(:) = v%elements(:)  ! { dg-error "is not a member of" }
24    end select
25
26  end subroutine bar
27
28end
29