aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/typebound_call_18.f03
blob: e417ebf9189e81a3c3e2a17c8f7ee526d6f9e77c (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
64
65
! { dg-do run }
!
! PR 45271: [OOP] Polymorphic code breaks when changing order of USE statements
!
! Contributed by Harald Anlauf <anlauf@gmx.de>

module abstract_vector
  implicit none
  type, abstract :: vector_class
  contains
    procedure(op_assign_v_v), deferred :: assign
  end type vector_class
  abstract interface
    subroutine op_assign_v_v(this,v)
      import vector_class
      class(vector_class), intent(inout) :: this
      class(vector_class), intent(in)    :: v
    end subroutine
  end interface
end module abstract_vector

module concrete_vector
  use abstract_vector
  implicit none
  type, extends(vector_class) :: trivial_vector_type
  contains
    procedure :: assign => my_assign
  end type
contains
  subroutine my_assign (this,v)
    class(trivial_vector_type), intent(inout) :: this
    class(vector_class),        intent(in)    :: v
    write (*,*) 'Oops in concrete_vector::my_assign'
    call abort ()
  end subroutine
end module concrete_vector

module concrete_gradient
  use abstract_vector
  implicit none
  type, extends(vector_class) :: trivial_gradient_type
  contains
    procedure :: assign => my_assign
  end type
contains
  subroutine my_assign (this,v)
    class(trivial_gradient_type), intent(inout) :: this
    class(vector_class),          intent(in)    :: v
    write (*,*) 'concrete_gradient::my_assign'
  end subroutine
end module concrete_gradient

program main
  !--- exchange these two lines to make the code work:
  use concrete_vector    ! (1)
  use concrete_gradient  ! (2)
  !---
  implicit none
  type(trivial_gradient_type)      :: g_initial
  class(vector_class),  allocatable :: g
  print *, "cg: before g%assign"
  allocate(trivial_gradient_type :: g)
  call g%assign (g_initial)
  print *, "cg: after  g%assign"
end program main