F_c_string function

In the thread on Best practices for passing C strings, Steve Lionel mentioned that the next standard release will include the function f_c_string, with the following specification:

F_C_STRING (STRING [, ASIS])

Description: Copy a string with appended NUL

Class: Transformational function

STRING shall be a character scalar of default kind or of kind C_CHAR.

ASIS (optional) shall be a logical scalar.

Result characteristics: The result is of type character with
the same kind type parameter as STRING.

Result value:

Case (i): If ASIS is not present or has the value false, the value
of the result is the value of TRIM(STRING)// CHAR(0,KIND(STRING)).
The length type parameter is one greater than the length
of STRING less the number of trailing blanks in STRING.

Case (ii): If ASIS is present with the value true, the
value of the result is the value of STRING with CHAR(0,KIND(STRING))
appended. The length type parameter of the result is one greater
than the length of STRING.

I have started using this function in some of my codes, with the following implementation:

  function f_c_string(string,asis)
    use, intrinsic :: iso_c_binding, only: c_char,c_null_char
    character(len=*), intent(in) :: string
    logical, intent(in), optional :: asis

    character(kind=c_char,len=:), allocatable :: f_c_string
    logical :: asis_

    asis_ = .false.
    if (present(asis)) asis_ = asis

    if (asis_) then
      f_c_string = string//c_null_char
    else
      f_c_string = trim(string)//c_null_char
    end if

  end function

Some questions I have are:

  1. Is there any reason to replace c_null_char with char(0,kind(string))?
  2. Can the length of the result string be fixed in advance? I have tried to achieve this with the declaration:
    character(kind=c_char,len = &
      merge(len(string) + 1, len_trim(string) + 1, &
        merge(asis,.false.,present(asis)))) :: f_c_string

however the compiler returns with an error.

ipribec@ipribec-T530:~/fortran/Rfortran$ gfortran -c f_c_string.f90 
f_c_string.f90:9:14:

    9 |         merge(asis,.false.,present(asis)))) :: f_c_string
      |              1
Error: Dummy argument ‘asis’ at (1) cannot be OPTIONAL

I just realized that fixed-length strings can be used but the procedure must be split into two procedures and placed under a generic interface:

  function f_c_string_default(string) result(f_c_string)
    use, intrinsic :: iso_c_binding, only: c_char,c_null_char
    character(len=*), intent(in) :: string

    character(kind=c_char,len=len_trim(string)+1) :: f_c_string

    f_c_string = trim(string)//c_null_char

  end function

  function f_c_string_asis(string,asis) result(f_c_string)
    use, intrinsic :: iso_c_binding, only: c_char,c_null_char
    character(len=*), intent(in) :: string
    logical, intent(in) :: asis

    character(kind=c_char,len = &
      merge(len(string) + 1, len_trim(string) + 1, asis)) :: f_c_string

    if (asis) then
      f_c_string = string//c_null_char
    else
      f_c_string = trim(string)//c_null_char
    end if

  end function
1 Like

These may not be the same if C_CHAR is not the same as default character. The proposed function accepts either default character or kind C_CHAR.