c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / submodule_26.f08
blob6e0ec9a8f3962d2bf6c1abc882f4114a85a80314
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
4 ! Tests the fix for PR71838 in which the PROCEDURE dummy argument caused
5 ! an ICE in the submodule. This is the reduced test in comment #9.
7 ! Contributed by Anton Shterenlikht  <mexas@bristol.ac.uk>
8 ! Test reduced by Dominique d'Humieres <dominiq@lps.ens.fr>
10 module cgca_m3clvg
11   abstract interface
12     subroutine cgca_clvgs_abstract( farr, marr, n, cstate, debug,      &
13                                     newstate )
14       integer, parameter :: iarr = 4, idef = 4, rdef = 4, ldef = 4
15       integer, parameter :: l=-1, centre=l+1, u=centre+1
16       integer( kind=iarr ), intent(in) :: farr(l:u,l:u,l:u),           &
17           marr(l:u,l:u,l:u), cstate
18       real( kind=rdef ), intent(in) :: n(3)
19       logical( kind=ldef ), intent(in) :: debug
20       integer( kind=iarr ), intent(out) :: newstate
21      end subroutine cgca_clvgs_abstract
22   end interface
24   interface
25     module subroutine cgca_clvgp( coarray, rt, t, scrit, sub, gcus,    &
26                                  periodicbc, iter, heartbeat, debug )
27       integer, parameter :: iarr = 4, idef = 4, rdef = 4, ldef = 4
28       integer( kind=iarr ), allocatable, intent(inout) ::              &
29           coarray(:,:,:,:)[:,:,:]
30       real( kind=rdef ), allocatable, intent(inout) :: rt(:,:,:)[:,:,:]
31       real( kind=rdef ), intent(in) :: t(3,3), scrit(3)
32       procedure( cgca_clvgs_abstract ) :: sub
33       logical( kind=ldef ), intent(in) :: periodicbc
34       integer( kind=idef ), intent(in) :: iter, heartbeat
35       logical( kind=ldef ), intent(in) :: debug
36     end subroutine cgca_clvgp
37   end interface
38 end module cgca_m3clvg
41 submodule ( cgca_m3clvg ) m3clvg_sm3
42   implicit none
43 contains
44   module procedure cgca_clvgp
45   end procedure cgca_clvgp
46 end submodule m3clvg_sm3