aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/typebound_call_17.f03
blob: 59968576256479829523c13ee6667783784ad806 (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
! { dg-do run }
!
! PR 44912: [OOP] Segmentation fault on TBP
!
! Contributed by Satish.BD <bdsatish@gmail.com>

module polynomial
implicit none

private

type, public :: polynom
   complex, allocatable, dimension(:) :: a
   integer :: n
 contains
   procedure :: init_from_coeff
   procedure :: get_degree
   procedure :: add_poly
end type polynom

contains
  subroutine init_from_coeff(self, coeff)
    class(polynom), intent(inout) :: self
    complex, dimension(:), intent(in) :: coeff
    self%n = size(coeff) - 1
    allocate(self%a(self%n + 1))
    self%a = coeff
    print *,"ifc:",self%a
  end subroutine init_from_coeff

  function get_degree(self)   result(n)
    class(polynom), intent(in) :: self
    integer :: n
    print *,"gd"
    n = self%n
  end function get_degree

  subroutine add_poly(self)
    class(polynom), intent(in) :: self
    integer :: s
    print *,"ap"
    s = self%get_degree()         !!!! fails here
  end subroutine

end module polynomial

program test_poly
   use polynomial, only: polynom

   type(polynom) :: p1

   call p1%init_from_coeff([(1,0),(2,0),(3,0)])
   call p1%add_poly()

end program test_poly