PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / no_arg_check_1.f90
blob1e1855d3174f23691684abf6dd983199c2685190
1 ! { dg-do compile }
3 ! PR fortran/39505
4 !
5 ! Test NO_ARG_CHECK
6 ! Copied from assumed_type_1.f90
8 module mpi_interface
9 implicit none
11 interface !mpi_send
12 subroutine MPI_Send (buf, count, datatype, dest, tag, comm, ierr)
13 !GCC$ attributes NO_ARG_CHECK :: buf
14 integer, intent(in) :: buf
15 integer, intent(in) :: count
16 integer, intent(in) :: datatype
17 integer, intent(in) :: dest
18 integer, intent(in) :: tag
19 integer, intent(in) :: comm
20 integer, intent(out):: ierr
21 end subroutine
22 end interface
24 interface !mpi_send2
25 subroutine MPI_Send2 (buf, count, datatype, dest, tag, comm, ierr)
26 !GCC$ attributes NO_ARG_CHECK :: buf
27 type(*), intent(in) :: buf(*)
28 integer, intent(in) :: count
29 integer, intent(in) :: datatype
30 integer, intent(in) :: dest
31 integer, intent(in) :: tag
32 integer, intent(in) :: comm
33 integer, intent(out):: ierr
34 end subroutine
35 end interface
37 end module
39 use mpi_interface
40 real :: a(3)
41 integer :: b(3)
42 call foo(a)
43 call foo(b)
44 call foo(a(1:2))
45 call foo(b(1:2))
46 call MPI_Send(a, 1, 1,1,1,j,i)
47 call MPI_Send(b, 1, 1,1,1,j,i)
48 call MPI_Send2(a, 1, 1,1,1,j,i)
49 call MPI_Send2(b, 1, 1,1,1,j,i)
50 contains
51 subroutine foo(x)
52 !GCC$ attributes NO_ARG_CHECK :: x
53 real :: x(*)
54 call MPI_Send2(x, 1, 1,1,1,j,i)
55 end
56 end