Visible to Intel only — GUID: GUID-AE650132-EA31-4C40-B2A2-D97A5DE1DFE0
Visible to Intel only — GUID: GUID-AE650132-EA31-4C40-B2A2-D97A5DE1DFE0
C_F_STRPOINTER
Intrinsic Module Subroutine (Generic): Associates a Fortran character data pointer with a C string.
Module
USE, INTRINSIC :: ISO_C_BINDING
Syntax
CALL C_F_STRPOINTER(cstrarray, fstrptr [, nchars])
-or-
CALL C_F_STRPOINTER(cstrptr, fstrptr [, nchars])
cstrarray |
(Input) Is a scalar rank 1 character array of type C_CHAR, with a length type parameter of one. The actual argument must have the TARGET attribute and be simply contiguous; it must be of derived type C_PTR. |
cstrptr |
(Input) Is a scalar with type C_PTR. It has the value of the C address of a contiguous array STRING containing nchars characters. It must not have a value that is the C address of a Fortran variable that does not have the TARGET attribute. |
fstrptr |
(Output) Is a deferred-length character pointer whose kind type is C_CHAR. If cstrarray appears, fstrptr becomes pointer-associated with the leftmost characters of the actual argument. If cstrptr appears, fstrptr becomes pointer-associated with the leftmost characters, in array element order, of STRING. The length type parameter of fstrptr becomes the largest value for which no C null characters appear in the sequence, and is less than or equal to nchars if it is present; otherwise, it is the size of cstrarray. |
nchars |
(Optional, input) Must be of type integer with a nonnegative value. It must be present if cstrarray is assumed-size, or if cstrptr appears. If cstrarray appears, nchars must not have a value greater than the size of cstrarray. |
Examples
The following procedure prints the value of up to the first 2048 characters of the PATH environment variable returned by calling the C library function getenv:
SUBROUTINE print_path () BIND (C)
USE ISO_C_BINDING
TYPE (C_PTR) :: getenv_res
CHARACTER(LEN=:,KIND=C_CHAR),POINTER :: path
INTERFACE
FUNCTION getenv (env_var) BIND (C)
IMPORT C_PTR, C_CHAR
TYPE (C_PTR) :: getenv
CHARACTER(KIND=C_CHAR),INTENT(IN) :: env_var (*)
END FUNCITON
END INTERFACE
getenv_res = getenv (“PATH”//C_NULL_CHAR)
IF (.NOT. C_ASSOCIATED (getenv_res)) THEN
PRINT *, “PATH not set”
ELSE
CALL C_F_STRPOINTER (getenv_res, path, 2048)
PRINT *, TRIM (path)
END IF
END SUBROUTINE print_path
The following procedure writes a C string to a Fortran internal file. The string can be of any length. The nchars argument in the call to C_F_POINTER limits the length of f_char_ptr to no more than n_chars characters, which is the maximum length of the internal file:
SUBROUTINE write_string (c_string, i_file) BIND (C)
USE ISO_C_BINDING
CHARACTER(LEN=:),INTENT(OUT) :: i_file
CHARACTER(LEN=:,KIND=C_CHAR),TARGET,INTENT(IN) :: c_string
CHARACTER(LEN=:,KIND=C_CHAR),POINTER :: f_char_ptr
INTEGER :: n_chars
n_chars = LEN(i_file)
CALL C_F_STRPOINTER (c_string, f_char_ptr, n_chars)
PRINT i_file, f_char_ptr
END SUBROUTINE write_string