Calling C from Fortran: Passing Vector of Strings from C to Fortran

Here is how I would do it. Similar code has worked for me in
the past.

Subroutine foo(names, names_n, ierr)

  USE ISO_C_BINDING

  Integer , Parameter :: MAX_STRING_LEN = 120
  Character(LEN=MAX_STRING_LEN), ALLOCATABLE, Intent(INOUT) :: names(:)
  Integer,                                    Intent(INOUT) :: names_n
  Integer,                                    Intent(INOUT) :: ierr


  Integer           :: i, inull, iend
  Integer(C_SIZE_T) :: names_n_c
  Integer(C_INT)    :: ierr_c
  Type(C_PTR)       :: names_c

  Type(C_PTR),                 Pointer :: cstring_p(:)
  Character(MAX_STRING_LEN+1), Pointer :: string_p

  Interface

    Subroutine foo_c(names, names_n, ierr) BIND(C,name="foo_c")

      IMPORT :: C_PTR, C_SIZE_T, C_INT

      Type(C_PTR),       Intent(INOUT) :: names
      Integer(C_SIZE_T), Intent(INOUT) :: names_n
      Integer(C_INT),    Intent(INOUT) :: ierr

    End Subroutine foo_c

  End Interface

  names_c = C_NULL_PTR
  names_n = 0

  Call foo_c(names_c, names_n_c, ierr_c)

  ierr    = ierr_c
  names_n = INT(names_n_c)
  If (C_ASSOCIATED(names_c)) Then
    CALL C_F_POINTER(names_c, cstring_p,[names_n])
    ALLOCATE(names(names_n))
    NULLIFY(string_p)
   Do i=1,names_n
      names(i) = REPEAT(" ",MAX_STRING_LEN)
      If (C_ASSOCIATED(cstring_p(i))) Then
        Call C_F_POINTER(cstring_p(i), string_p)
        inull = INDEX(string_p,C_NULL_CHAR)
        iend  = LEN_TRIM(string_p)
        If (inull /= 0) iend = inull-1
        iend = MAX(1,iend)
        names(i) = string_p(1:iend)
        NULLIFY(string_p)
      End If
    End Do
  End If
  Do i=1, names_n
    cstring_p(i) = C_NULL_PTR
  End Do

End Subroutine foo