Fortran Wiki
Generating C Interfaces

Contents


Introduction

Interfacing C is an essential feature in making Fortran a more useful programming tool. With heterogeneous code, Fortran can do what it does best, while leaving other tasks to better suited programming languages.

Developing C interfaces manually is time consuming and requires a significant effort to maintain. The best approach is to develop a good interface-generator tool. In order to develop a successful interface tool, the first step is to decide how C should be interfaced.

Design Requirements

These are Joe Krahn’s suggestions for a good C interface design. Feel free to extend or modify it, or include comments about caveats and alternatives.

  1. The Fortran user API should have minimal exposure to C types.
  2. Conversion of strings between Fortran and C should be handled by auto-generated wrapper functions.
  3. Access to Fortran array dimensions should not use non-portable access to internal compiler data structures.
  4. The process should be as automatic as possible. This is not easy for a proper interface because C prototypes often do not fully describe arguments. Standard Annotation Language is very beneficial, but not widely used outside of Microsoft.

Issues

  • Some C functions that accept string arguments can benefit from prototypes using both CHARACTER passed by reference and TYPE(C_PTR). I don’t know if Fortran 2008 supports multiple INTERFACE specifications bound to the same C function. In Fortran 2003, it was ambiguous.

Wrapper Functions

Many people see iso_c_binding as a way to avoid wrapper functions when calling C procedures. That is true in some cases, but often leads to verbose code containing explicit ISO-C declarations, rather than presenting a nice Fortran interface to the user.

Wrapper functions are the way to go. Swig is a widely used tool to generate software interfaces. The generated interfaces deal with data conversions. For example, a Swig interface for Fortran would include string conversions, deal with all array data structures, and proxy derived-type information.

Although Swig is a useful approach, building an interface is also a fairly involved process. We need to an interface-generating tool that efficiently builds interfaces for common, simple code interfaces. This will help work out the important design issues. Eventually, Swig can be extended to Fortran to deal with more advanced programming (e.g. OOP and sub-classed derived-types).

Here is an example interface specification for calling an HDF5 C function. The comment at the beginning is the C prototype. In this design, C functions all include a ‘c’ suffix, and could be called directly if the caller wants to avoid the wrapper dependency.

! herr_t H5Lcopy( hid_t src_loc, const char *src_name, hid_t dst_loc,  \\
!    const char *dst_name, hid_t lcpl_id, hid_t lapl_id);
  interface
    integer(herr_t) &
    function H5Lcopy_c(src_loc, src_name, dst_loc, dst_name, lcpl_id, &
        lapl_id) &
        bind(C,name="H5Lcopy")
      import C_char, herr_t, hid_t
      integer(hid_t), value, intent(in) :: src_loc
      character(len=1,kind=C_char), dimension(*), intent(in) :: src_name
      integer(hid_t), value, intent(in) :: dst_loc
      character(len=1,kind=C_char), dimension(*), intent(in) :: dst_name
      integer(hid_t), value, intent(in) :: lcpl_id
      integer(hid_t), value, intent(in) :: lapl_id
    end function H5Lcopy_c
  end interface

Here is the corresponding wrapper code that handles Fortran-to-C string conversion.


! herr_t H5Lcopy( hid_t src_loc, const char *src_name, hid_t dst_loc,  \\
!    const char *dst_name, hid_t lcpl_id, hid_t lapl_id);
  subroutine H5Lcopy(src_loc, src_name, dst_loc, dst_name, lcpl_id, &
      lapl_id, hdferr)
    integer(hid_t), intent(in) :: src_loc
    character(len=*), intent(in) :: src_name
    integer(hid_t), intent(in) :: dst_loc
    character(len=*), intent(in) :: dst_name
    integer(hid_t), intent(in) :: lcpl_id
    integer(hid_t), intent(in) :: lapl_id
    integer(herr_t), intent(out), optional :: hdferr
    integer(herr_t) :: hdferr_
    hdferr_ = H5Lcopy_c(src_loc, trim(src_name)//NUL, dst_loc, &
        trim(dst_name)//NUL, lcpl_id, lapl_id)
    if (present(hdferr)) then
      hdferr = hdferr_
      return
    else if (.not.(hdferr_ >= 0)) then
      call hdf5_throw("H5Lcopy",hdferr_)
    end if
  end subroutine H5Lcopy

C++ class wrappers

The main drawback of interfacing C++ classes is that function overloading can combine void and non-void types, whereas Fortran does not allow mixing of function and subroutine types under the same generic name (IMHO, a serious design flaw).

Here is an example of providing an OOP interface to the FLTK C++ library. This shows just the user code, not the interfaces or wrapper code. The design is for all objects to be instantiated under the common generic subroutine new. All OOP functions give the object as the first argument, so there is never a procedure-matching conflict among different types, except for the subroutine/function design flaw.

This is a simple C++ FLTK example:

#include <stdio.h>
#include <FL/Fl_Button.H>
#include <FL/Fl_Window.H>
#include <FL/Fl_Input_Choice.H>

void buttcb(Fl_Widget*,void*data) {
    Fl_Input_Choice *in=(Fl_Input_Choice *)data;
    static int flag = 1;
    flag ^= 1;
    if ( flag ) in->activate();
    else        in->deactivate();
}

void input_choice_cb(Fl_Widget*,void*data) {
    Fl_Input_Choice *in=(Fl_Input_Choice *)data;
    fprintf(stderr, "Value='%s'\
", (const char*)in->value());
}

int main(int argc, char **argv) {
    Fl::scheme("plastic");              // optional
    Fl_Window win(300, 200);

    Fl_Input_Choice in(40,40,100,28,"Test");
    in.callback(input_choice_cb, (void*)&in);
    in.add("one");
    in.add("two");
    in.add("three");
    in.value(1);

    Fl_Button onoff(40,150,200,28,"Activate/Deactivate");
    onoff.callback(buttcb, (void*)&in);

    win.end();
    win.resizable(win);
    win.show(argc, argv);
    return Fl::run();
}

This is the Fortran 90 equivalent. To achieve a user-friendly Fortran interface, some procedures require both Fortran and C wrapper routines. The C wrapper routines are mainly proxies between C and C++ call conventions and C++ function overloading (e.g. name-mangled symbols).

With Fortran 2003 type-bound procedures, the Fortran interface will appear even more like the C++ interface. However, generic procedure names do a good job of providing a clean interface.

subroutine button_cb(widget,data)
  use fltk
  type(FL_Widget) :: widget
  type(FL_Void) :: data
  type(Fl_Input_Choice) :: in
  logical, save :: flag = .true.
  in=data
  flag = .not. flag
  if ( flag ) then
    call activate(in)
  else
    call deactivate(in)
  end if
end subroutine button_cb

subroutine input_choice_cb(widget,data)
  use fltk
  type(FL_Widget) :: widget
  type(FL_Void) :: data
  type(Fl_Input_Choice) :: in
  in = data
  write(0,'(2A)') "Value=",get_value(in)
end subroutine input_choice_cb

program main
  use fltk
  type(Fl_Window) :: win
  type(Fl_Input_Choice) :: in
  type(Fl_Button) :: onoff
  external input_choice_cb,button_cb

  call Fl_scheme("plastic") ! optional
  call new(win,300,200)
  call new(in,40,40,100,28,"Test")
  call add(in,"one")
  call add(in,"two")
  call add(in,"three")
  call value(in,1)
  call new(onoff,40,150,200,28,"Activate/Deactivate");
  call callback(onoff, button_cb,FL_Void_type)
  call end(win)
  call resizable(win,win)
  call show(win)
  call Fl_run()
end program main

String Handling

Typical examples of using iso_c_binding pass strings as follows:

  CALL C_FUNC(TRIM(F_STRING)//C_NULL_CHAR)

The approach above requires F_STRING to be KIND=C_CHAR. In most cases, the C_CHAR kind will be the same as the default kind, but this should not be relied on for portable code. Instead, a Fortran wrapper function can convert from default kind to C_CHAR as follows, using a local temporary copy:

  CHARACTER(LEN=LEN_TRIM(F_STRING)+1,KIND=C_CHAR) :: C_STRING
  C_STRING = TRIM(F_STRING)//C_NULL_CHAR
  CALL C_FUNC(C_STRING)

Note that in both cases, a temporary string is created, so this method adds portability with no overhead. An intrinsic CHAR(_string_,_kind_) function would simplify this. A helper function can convert the character kind specific for Fortran-to-C as follows:

  PURE FUNCTION F_C_STRING_FUNC(F_STRING) RESULT(C_STRING)
    USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_CHAR, C_NULL_CHAR
    IMPLICIT NONE
    CHARACTER(LEN=*), INTENT(IN) :: F_STRING
    CHARACTER(LEN=1,KIND=C_CHAR) :: C_STRING(LEN_TRIM(F_STRING)+1)
    C_STRING = F_STRING // C_NULL_CHAR
  END FUNCTION F_C_STRING_FUNC

Unfortunately, on at least the GNU and Intel compilers, the statement

    C_STRING = F_STRING // C_NULL_CHAR

causes C_STRING to contain LEN_TRIM(F_STRING) copies of F_STRING’s first character followed by a null character. Explicitly copying each character as follows seems to be required:

  PURE FUNCTION F_C_STRING_FUNC (F_STRING) RESULT (C_STRING)
    USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_CHAR, C_NULL_CHAR
    IMPLICIT NONE
    CHARACTER(LEN=*), INTENT(IN) :: F_STRING
    CHARACTER(LEN=1,KIND=C_CHAR) :: C_STRING(LEN_TRIM(F_STRING)+1)
    INTEGER                      :: N, I

    N = LEN_TRIM(F_STRING)
    DO I = 1, N
      C_STRING(I) = F_STRING(I:I)
    END DO
    C_STRING(N + 1) = C_NULL_CHAR

  END FUNCTION F_C_STRING_FUNC

The DO loop seems mandatory. The trivial slice F_STRING(I:I) admittedly looks odd but is also necessary– F_STRING(I) is parsed as an invalid function call and fails to compile.

An important question is whether to treat strings as blank-padded, or require the caller to pass only the “valid” part of the string. Another problem is how to return strings of varying length. There could be a length return value, like GET_COMMAND_ARGUMENT. A better option is to use allocatable-length strings, but they are not yet widely supported.

The right answer is probably not to use a single method. If a string argument can have significant terminal blanks, the above examples will not work. Otherwise, the automatic-trimming method is a simplification for the caller, at least until variable-length strings become the norm in Fortran.

Discussion

  • Why is C_STRING declared as an array? This is definitely necessitating the loop because you are trying to assign a scalar object to an array. Does the following not work?
    :
    CHARACTER(len=LEN_TRIM(f_String)+1,kind=C_CHAR) :: c_string
    :
    c_string = TRIM(f_string) // C_NULL_CHAR

    I can’t remember if Fortran doesn’t like character functions whose return argument’s len parameter is not a compile time constant. One possible work around would be to make the return variable an allocatable scalar, which should be kosher according F2003. –IzaakBeekman