OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [typebound_call_17.f03] - Blame information for rev 704

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do run }
2
!
3
! PR 44912: [OOP] Segmentation fault on TBP
4
!
5
! Contributed by Satish.BD 
6
 
7
module polynomial
8
implicit none
9
 
10
private
11
 
12
type, public :: polynom
13
   complex, allocatable, dimension(:) :: a
14
   integer :: n
15
 contains
16
   procedure :: init_from_coeff
17
   procedure :: get_degree
18
   procedure :: add_poly
19
end type polynom
20
 
21
contains
22
  subroutine init_from_coeff(self, coeff)
23
    class(polynom), intent(inout) :: self
24
    complex, dimension(:), intent(in) :: coeff
25
    self%n = size(coeff) - 1
26
    allocate(self%a(self%n + 1))
27
    self%a = coeff
28
    print *,"ifc:",self%a
29
  end subroutine init_from_coeff
30
 
31
  function get_degree(self)   result(n)
32
    class(polynom), intent(in) :: self
33
    integer :: n
34
    print *,"gd"
35
    n = self%n
36
  end function get_degree
37
 
38
  subroutine add_poly(self)
39
    class(polynom), intent(in) :: self
40
    integer :: s
41
    print *,"ap"
42
    s = self%get_degree()         !!!! fails here
43
  end subroutine
44
 
45
end module polynomial
46
 
47
program test_poly
48
   use polynomial, only: polynom
49
 
50
   type(polynom) :: p1
51
 
52
   call p1%init_from_coeff([(1,0),(2,0),(3,0)])
53
   call p1%add_poly()
54
 
55
end program test_poly
56
 
57
! { dg-final { cleanup-modules "polynomial" } }

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.