aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/dummy_procedure_7.f90
blob: 0e5b7d9eef14a2722358318a8def876470907b15 (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 run }
!
! PR fortran/52022
!

module check
  integer, save :: icheck = 0
end module check

module t
implicit none
      contains
subroutine  sol(cost)
   use check
   interface 
        function cost(p) result(y) 
                double precision,dimension(:) :: p
                double precision,dimension(:),allocatable :: y
        end function cost
   end interface

   if (any (cost([1d0,2d0]) /= [2.d0, 4.d0])) call abort ()
   icheck = icheck + 1
end subroutine

end module t

module tt
   procedure(cost1),pointer :: pcost
contains
  subroutine init()
        pcost=>cost1
  end subroutine

  function cost1(x) result(y)
        double precision,dimension(:) :: x
        double precision,dimension(:),allocatable :: y
        allocate(y(2))
        y=2d0*x
  end function cost1



  function cost(x) result(y)
        double precision,dimension(:) :: x
        double precision,dimension(:),allocatable :: y
        allocate(y(2))
        y=pcost(x)
  end function cost
end module

program test
        use tt
        use t
        use check
        implicit none

        call init()
        if (any (cost([3.d0,7.d0]) /= [6.d0, 14.d0])) call abort ()
        if (icheck /= 0) call abort ()
        call sol(cost)
        if (icheck /= 1) call abort ()
end program test