aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/abstract_type_9.f90
blob: 77d48ba61f5a73440225f3c1cf420aa9d0abdcdf (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
! { dg-do compile }
!
! PR 43207: [OOP] invalid (pointer) assignment to and from abstract non-polymorphic expressions
!
! Contributed by Tobias Burnus <burnus@gcc.gnu.org>

  implicit none
  type, abstract :: parent
    integer :: i
  end type
  type, extends(parent) :: child
    class(parent), pointer :: comp
  end type

  type(child), target :: c1
  class(child), allocatable :: c2
  class(parent), pointer :: cp

  c1%parent = c1%parent  ! { dg-error "Nonpolymorphic reference to abstract type" }
  c2%parent = c1%parent  ! { dg-error "Nonpolymorphic reference to abstract type" }

  cp => c1%comp
  cp => c1%parent        ! { dg-error "Nonpolymorphic reference to abstract type" }

  call sub(c1%comp)
  call sub(c1%parent)    ! { dg-error "Nonpolymorphic reference to abstract type" }

contains

  subroutine sub(arg)
    class(parent) :: arg
  end subroutine

end