PROGRAM CandF ! Program to test cooperation between C and Fortran USE, INTRINSIC :: iso_c_binding CALL check(c_int, KIND(1), 'integer/int') CALL check(c_float, KIND(1.0e0), 'real/float') CALL check(c_double, KIND(1.0d0), 'double precision/double') CALL check(c_bool, KIND(.TRUE.), 'logical/boolean') CALL check(c_char, KIND('A'), 'character/char') CALL check(c_float_complex, KIND((1.0e0, 1.0e0)), 'complex/float_complex') END Program CandF SUBROUTINE check(ckind, fkind, vartype) INTEGER, INTENT(IN) :: ckind, fkind CHARACTER (LEN=*), INTENT(IN) :: vartype IF (ckind == fkind) THEN WRITE(*,'(''Default Fortran and C variables of type '', a, & &'' are interoperable'')') vartype ELSE IF (ckind < 0) THEN WRITE(*, & '(''A compatible Fortran kind value is not available for type '' & &, a)'')') vartype ELSE WRITE(*,'(''Default Fortran and C variables of type '', a, & &'' are NOT interoperable'')') vartype END IF END SUBROUTINE check