arm: Add .type and .size to __gnu_cmse_nonsecure_call [PR115360]
[official-gcc.git] / gcc / testsuite / gfortran.dg / spec_expr_10.f90
blob287b5a8d6ccc6c12a5858515f6f865915b65e249
1 ! { dg-do compile }
3 ! PR fortran/114475
4 ! The array specification of PP in OL_EVAL used to be rejected in the submodule
5 ! because the compiler was not able to see the host-association of N_EXTERNAL
6 ! there.
8 ! Contributed by Jürgen Reuter <juergen.reuter@desy.de>.
10 module t1
11 use, intrinsic :: iso_c_binding
12 implicit none
13 private
14 public :: t1_t
15 integer :: N_EXTERNAL = 0
17 type :: t1_t
18 contains
19 procedure :: set_n_external => t1_set_n_external
20 end type t1_t
22 abstract interface
23 subroutine ol_eval (id, pp, emitter) bind(C)
24 import
25 real(kind = c_double), intent(in) :: pp(5 * N_EXTERNAL)
26 end subroutine ol_eval
27 end interface
28 interface
29 module subroutine t1_set_n_external (object, n)
30 class(t1_t), intent(inout) :: object
31 integer, intent(in) :: n
32 end subroutine t1_set_n_external
33 end interface
35 end module t1
37 submodule (t1) t1_s
38 implicit none
39 contains
40 module subroutine t1_set_n_external (object, n)
41 class(t1_t), intent(inout) :: object
42 integer, intent(in) :: n
43 N_EXTERNAL = n
44 end subroutine t1_set_n_external
46 end submodule t1_s