Filling a fixed-size string in a C-interoperable type

I’m calling a C function from Fortran that takes a C struct as argument:

struct Params
{
    char p1[64];
    char p2[64];
}

void my_function(const struct Params *);

I’m binding it this way:

  use iso_c_binding, only: c_char, c_null_char

  type, bind(c) :: Params
    character(kind=c_char) p1(64), p2(64)
  end type
  
  interface
    subroutine my_function(p) bind(c)
      import :: Params
      type(Params), intent(in) :: p
    end
  end interface

But I can’t figure out how to initialize the string members:

  type(Params) :: p
  
  p%p1 = "abcdef" // c_null_char
  p%p2 = "/dev/ttyUSB0" // c_null_char

This generates a CHARACTER expression will be truncated in assignment compilation warning, and this result is p%p1 being completly filled with a (and p%p2 with /), which is logical to given the array nature of p1.

This only way I found to make my assignment is by a loop and an intermediate string:

  integer i
  character(len=64) tmp
  
  tmp = "abcdef" // c_null_char
  do i=1,len_trim(tmp)
    p%p1(i:i) = tmp(i:i)
  enddo

But this is somewhat tedious. Isn’t there a simpler way to do this?

Full example

Fortran code:

program test_binding
  use iso_c_binding, only: c_char, c_null_char

  type, bind(c) :: Params
    character(kind=c_char) p1(64), p2(64)
  end type
  
  interface
    subroutine my_function(p) bind(c)
      import :: Params
      type(Params), intent(in) :: p
    end
  end interface

  type(Params) :: p
  integer i
  character(len=64) tmp
  
  tmp = "abcdef" // c_null_char
  do i=1,len_trim(tmp)
    p%p1(i:i) = tmp(i:i)
  enddo
  
  tmp = "/dev/ttyUSB0" // c_null_char
  do i=1,len_trim(tmp)
    p%p2(i:i) = tmp(i:i)
  enddo
  
  print *, p%p1
  print *, p%p2
  
  call my_function(p)

end program

C code:

#include <stdio.h>

struct Params
{
    char p1[64];
    char p2[64];
};

void my_function(const struct Params * p)
{
    printf("In C : '%s'\n", p->p1);
    printf("In C : '%s'\n", p->p2);
}

Build with e.g. gfortran -Wall -ffree-line-length-none test_binding.f90 test_c.c -o test_binding.

1 Like

Well, C strings are arrays, and that’s usually how they should be handled (unless they’re arguments).

Btw, character literals accept substring indices:

use ISO_C_BINDING

implicit none

type, bind(c) :: params
    character(KIND = C_CHAR) :: p1(64) = C_NULL_CHAR
    character(KIND = C_CHAR) :: p2(64) = C_NULL_CHAR
end type

integer :: n

type(params) :: p

n = 6
p%p1(:n) = [('abcdef'(i:i), integer :: i = 1, n)]

print*,'p1=',p%p1(:n)
end
1 Like

Perhaps the transfer intrinsic function can help? I have not written an example, but it should work.

transfer works indeed:

  character(len=64) tmp

  tmp = "abcdef" // c_null_char
  p%p1 = transfer(tmp, p%p1)

gives the expected result. Repeating p%p1 looks a bit strange, but it’s already simpler that my loop attempt.

Without a temporary, specifying bounds seems necessary:

  ! p%p1 = transfer("abcdef" // c_null_char, p%p1) ! Error: Different shape for array assignment at (1) on dimension 1 (64 and 7)
  p%p1(1:7) = transfer("abcdef" // c_null_char, p%p1) ! OK

I’m not familiar with the transfer function, not sure I’m using it correctly here.

1 Like

The second argument is used for the type of data that needs to be returned. This may be the reason for the shape error - the character length is also involved.

@nja, there is also an optional size parameter:

p%p1 =transfer("abcdef"//c_null_char,mold=p%p1,size=size(p%p1))

that will ensure the return argument has the same size as p1

1 Like

Within fortran, storage sequence association allows scalar character strings and character arrays to be interoperable. For example, I think the following code is standard conforming:

program  charlen
   character(8) :: c = '12345678'
   call sub( c, c, len(c) )
contains
   subroutine sub( cs, ca, n )
      character(*), intent(in) :: cs     ! scalar string
      character(1), intent(in) :: ca(n)  ! array
      character(*), parameter :: cfmt='(*(g0))'
      write(*,cfmt) 'len=', len(cs), ' n=', n
      write(*,cfmt) 'cs=', cs
      write(*,cfmt) 'ca=', ca
      return
   end subroutine sub
end program charlen

$ gfortran --warn-all charlen.f90 && a.out
len=8 n=8
cs=12345678
ca=12345678

Is it possible to use this feature to declare fortran scalar components that are interoperable with C char arrays?