1! { dg-do compile }
2! { dg-options "" }
3!
4! PR fortran/56378
5! PR fortran/52426
6!
7! Contributed by David Sagan & Joost VandeVondele
8!
9
10module t
11 use, intrinsic :: iso_c_binding
12 interface fvec2vec
13   module procedure int_fvec2vec
14 end interface
15contains
16 function int_fvec2vec (f_vec, n) result (c_vec)
17 integer f_vec(:)
18 integer(c_int), target :: c_vec(n)
19 end function int_fvec2vec
20 subroutine lat_to_c (Fp, C) bind(c)
21 integer, allocatable :: ic(:)
22 call lat_to_c2 (c_loc(fvec2vec(ic, n1_ic))) ! { dg-error "Argument X at .1. to C_LOC shall have either the POINTER or the TARGET attribute" }
23 end subroutine lat_to_c
24end module
25
26use iso_c_binding
27print *, c_loc([1]) ! { dg-error "Argument X at .1. to C_LOC shall have either the POINTER or the TARGET attribute" }
28end
29