• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1! RUN: %S/test_errors.sh %s %t %f18
2module m
3  type t1
4  end type
5  type t3
6  end type
7  interface
8    subroutine s1(x)
9      !ERROR: 't1' from host is not accessible
10      import :: t1
11      type(t1) :: x
12      integer :: t1
13    end subroutine
14    subroutine s2()
15      !ERROR: 't2' not found in host scope
16      import :: t2
17    end subroutine
18    subroutine s3(x, y)
19      !ERROR: Derived type 't1' not found
20      type(t1) :: x, y
21    end subroutine
22    subroutine s4(x, y)
23      !ERROR: 't3' from host is not accessible
24      import, all
25      type(t1) :: x
26      type(t3) :: y
27      integer :: t3
28    end subroutine
29  end interface
30contains
31  subroutine s5()
32  end
33  subroutine s6()
34    import, only: s5
35    implicit none(external)
36    call s5()
37  end
38  subroutine s7()
39    import, only: t1
40    implicit none(external)
41    !ERROR: 's5' is an external procedure without the EXTERNAL attribute in a scope with IMPLICIT NONE(EXTERNAL)
42    call s5()
43  end
44end module
45