summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/submodule_14.f08
blob: 329569966e47e246e029081a5738dbea48281072 (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
! { dg-do compile }
!
! Check the fix for PR70031, where the 'module' prefix had to preceed
! 'function/subroutine' in the interface (or in the CONTAINS section.
!
! As reported by "Bulova" on
! https://groups.google.com/forum/#!topic/comp.lang.fortran/hE8LkVMhghQ
!
module test
  Interface
    Module Recursive Subroutine sub1 (x)
      Integer, Intent (InOut) :: x
    End Subroutine sub1
    module recursive function fcn1 (x) result(res)
      integer, intent (inout) :: x
      integer :: res
    end function
  End Interface
end module test

submodule(test) testson
  integer :: n = 10
contains
  Module Procedure sub1
    If (x < n) Then
        x = x + 1
        Call sub1 (x)
    End If
  End Procedure sub1
  recursive module function fcn1 (x) result(res)
    integer, intent (inout) :: x
    integer :: res
    res = x - 1
    if (x > 0) then
      x = fcn1 (res)
    else
      res = x
    end if
  end function
end submodule testson

  use test
  integer :: x = 5
  call sub1(x)
  if (x .ne. 10) STOP 1
  x = 10
  if (fcn1 (x) .ne. 0) STOP 2
end