aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_7.f90
blob: 9c960dda21e28cd83e7ece5545708cd3708c3a40 (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
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
! { dg-do compile }
!
! PR 46662: [OOP] gfortran accepts "CALL polymorphic%abstract_type%ppc()"
!
! Contributed by Wolfgang Kilian <kilian@hep.physik.uni-siegen.de>
! cf. http://groups.google.com/group/comp.lang.fortran/browse_thread/thread/a0857fa4a692d518

module types
  implicit none

  type, abstract :: base_t
     integer :: i = 0
     procedure(base_write_i), pointer :: write_procptr
   contains
     procedure :: write_i => base_write_i
  end type base_t

  type, extends (base_t) :: t
  end type t

contains

  subroutine base_write_i (obj)
    class (base_t), intent(in) :: obj
    print *, obj%i
  end subroutine base_write_i

end module types


program main
  use types
  implicit none

  type(t) :: obj

  print *, "Direct printing"
  obj%i = 1
  print *, obj%i

  print *, "Direct printing via parent"
  obj%base_t%i = 2
  print *, obj%base_t%i

  print *, "Printing via TBP"
  obj%i = 3
  call obj%write_i

  print *, "Printing via parent TBP"
  obj%base_t%i = 4
  call obj%base_t%write_i      ! { dg-error "is of ABSTRACT type" }

  print *, "Printing via OBP"
  obj%i = 5
  obj%write_procptr => base_write_i
  call obj%write_procptr

  print *, "Printing via parent OBP"
  obj%base_t%i = 6
  obj%base_t%write_procptr => base_write_i
  call obj%base_t%write_procptr               ! { dg-error "is of ABSTRACT type" }

end program main