SUBROUTINE c_sam(c_f, b, s) BIND(C, NAME='c_sam') USE, INTRINSIC :: iso_c_binding, ONLY : c_char, & c_int, c_null_char INTERFACE FUNCTION c_f(x) RESULT(f_res) BIND(C) USE, INTRINSIC :: iso_c_binding, ONLY : c_int, c_float INTEGER (c_int) :: f_res REAL (c_float) :: x END FUNCTION c_f END INTERFACE ! C requires that the string be one character longer than its Fortran ! equivalent as it needs to be null terminated. CHARACTER(KIND=c_char) :: s(8) ! C requires a stop character CHARACTER(len=7) :: t INTEGER (c_int) :: b INTEGER :: I CALL sam(c_f,b,t) DO I=1,7 s(I)=t(I:I) END DO s(8)=c_null_char ! End C string END SUBROUTINE c_sam FUNCTION c_f(x) RESULT (f_res) BIND(C,NAME='c_f') USE, INTRINSIC :: iso_c_binding, ONLY : c_int, c_float INTEGER (c_int) :: f_res REAL(c_float) :: x INTEGER, EXTERNAL :: f f_res=f(x) END FUNCTION c_f