How to use a shared/dynamically linked library in Fortran

Hi,
I have a neural network trained in Matlab. Now, I want to use this network in Fortran. So, I followed the instructions given here: https://www.mathworks.com/help/deeplearning/ref/network.genfunction.html:

%% First, train a static network and calculate its outputs for the training data.
[x,t] = bodyfat_dataset;
bodyfatNet = feedforwardnet(10);
bodyfatNet = train(bodyfatNet,x,t);
y = bodyfatNet(x);
%% Next, generate and test a MATLAB function. Then the new function is compiled to a shared/dynamically linked library with mcc.
genFunction(bodyfatNet,'bodyfatFcn');
y2 = bodyfatFcn(x);
accuracy2 = max(abs(y-y2))
mcc -W lib:libBodyfat -T link:lib bodyfatFcn

This leads to the generation of files with extensions .c, .h and .so

In the Fortran code test.F90, I want to be able to compute y_test for a given x_test:
y_test = bodyfatNet(x_test); Could you please tell me how this can be done/written?

Here below is my Makefile. I can make an executable from object file test.o and the shared object .so:

FORTRAN_COMPILER=gfortran
#FORTRAN_FLAGS=-O3 -Wall -Wextra -std=f2008 
FORTRAN_FLAGS=-ffree-line-length-none

OBJ2 = libBodyfat.so

SRC1= test.F90
OBJ1 = $(SRC1:.F90=.o)

LIBS     =  $(OBJ1) $(OBJ2)

%.o: %.F90
	@echo 'converting .F90 files to .o'
	$(FORTRAN_COMPILER) $(FORTRAN_FLAGS) -o $@ -c $<

binary: $(LIBS)
	@echo 'make an executable from objet files (.o) and the shared object (.so)'
	$(FORTRAN_COMPILER) $(FORTRAN_FLAGS) -o $@ $(LIBS)
clean:	
	@echo 'cleaning'
	@rm -f *.mod *.o binary

I am not certain if utilizing only ‘.so’ would suffice. But the more general question is how from test.F90 I can use the network.

1 Like

After my search, it seems that using the h file might be easier (please correct me if I am wrong). In libBodyfat.h, I can see that there are 6 functions. So, now the question is how to include C header in Fortran? How to call these functions? In which order? Should they all (libBodyfatInitialize, libBodyfatInitializeWithHandlers, libBodyfatTerminate, libBodyfatPrintStackTrace, mlxBodyfatFcn
mlfBodyfatFcn) be called ?

/*

  • MATLAB Compiler: 8.2 (R2021a)
  • Date: Wed Feb 8 15:21:13 2023
  • Arguments: “-B”“macro_default”“-W”“lib:libBodyfat”“-T”“link:lib”“bodyfatFcn”
    */

#ifndef libBodyfat_h
#define libBodyfat_h 1

#if defined(__cplusplus) && !defined(mclmcrrt_h) && defined(linux)

pragma implementation “mclmcrrt.h”

#endif
#include “mclmcrrt.h”
#ifdef __cplusplus
extern “C” { // sbcheck:ok:extern_c
#endif

/* This symbol is defined in shared libraries. Define it here

  • (to nothing) in case this isn’t a shared library.
    /
    #ifndef LIB_libBodyfat_C_API
    #define LIB_libBodyfat_C_API /
    No special import/export declaration */
    #endif

/* GENERAL LIBRARY FUNCTIONS – START */

extern LIB_libBodyfat_C_API
bool MW_CALL_CONV libBodyfatInitializeWithHandlers(
mclOutputHandlerFcn error_handler,
mclOutputHandlerFcn print_handler);

extern LIB_libBodyfat_C_API
bool MW_CALL_CONV libBodyfatInitialize(void);

extern LIB_libBodyfat_C_API
void MW_CALL_CONV libBodyfatTerminate(void);

extern LIB_libBodyfat_C_API
void MW_CALL_CONV libBodyfatPrintStackTrace(void);

/* GENERAL LIBRARY FUNCTIONS – END */

/* C INTERFACE – MLX WRAPPERS FOR USER-DEFINED MATLAB FUNCTIONS – START */

extern LIB_libBodyfat_C_API
bool MW_CALL_CONV mlxBodyfatFcn(int nlhs, mxArray *plhs, int nrhs, mxArray *prhs);

/* C INTERFACE – MLX WRAPPERS FOR USER-DEFINED MATLAB FUNCTIONS – END */

/* C INTERFACE – MLF WRAPPERS FOR USER-DEFINED MATLAB FUNCTIONS – START */

extern LIB_libBodyfat_C_API bool MW_CALL_CONV mlfBodyfatFcn(int nargout, mxArray** Y, mxArray** Xf, mxArray** Af, mxArray* X, mxArray* _U4b, mxArray* _U4c);

#ifdef __cplusplus
}
#endif
/* C INTERFACE – MLF WRAPPERS FOR USER-DEFINED MATLAB FUNCTIONS – END */

#endif

Try following the instructions given here: Call a C Shared Library - MATLAB & Simulink

Also note that a shared library requires you to specify the right option when compiling and linking. For gfortran that option is -shared. It is not enough to use a file extension “.so”.

Thanks Ivan. It is difficult for me to follow the instructions in the link that you sent as there is no example. I found this website with the two examples (kronrod and hello). However, when I try to apply the same logic to my test case, I fail. Do you know if there is any concrete example of using the matlab generated c functions in fortran?

My fortran code is:

subroutine main

use, intrinsic :: iso_c_binding
implicit none

interface
subroutine BodyfatInitialize ( ) bind ( c )
use iso_c_binding
end subroutine BodyfatInitialize
end interface

call BodyfatInitialize()
end subroutine main

program test_library
call main()
end program test_library

this leads to the error:

gfortran -ffree-line-length-none -o binary test2.o libBodyfat.o
test2.o: In function main_': test2.F90:(.text+0x5): undefined reference to bodyfatinitialize’
libBodyfat.o: In function mclDefaultPrintHandler': libBodyfat.c:(.text+0x28): undefined reference to mclWrite_proxy’
libBodyfat.o: In function mclDefaultErrorHandler': libBodyfat.c:(.text+0x6a): undefined reference to mclWrite_proxy’
libBodyfat.c:(.text+0xa0): undefined reference to mclWrite_proxy' libBodyfat.o: In function libBodyfatInitializeWithHandlers’:
libBodyfat.c:(.text+0xd7): undefined reference to mclmcrInitialize_proxy' libBodyfat.c:(.text+0xf1): undefined reference to mclGetEmbeddedCtfStream_proxy’
libBodyfat.c:(.text+0x117): undefined reference to mclInitializeComponentInstanceEmbedded_proxy' libBodyfat.c:(.text+0x129): undefined reference to mclDestroyStream_proxy’
libBodyfat.o: In function libBodyfatTerminate': libBodyfat.c:(.text+0x17b): undefined reference to mclTerminateInstance_proxy’
libBodyfat.o: In function libBodyfatPrintStackTrace': libBodyfat.c:(.text+0x1a1): undefined reference to mclGetStackTrace_proxy’
libBodyfat.c:(.text+0x1f0): undefined reference to mclWrite_proxy' libBodyfat.c:(.text+0x206): undefined reference to mclWrite_proxy’
libBodyfat.c:(.text+0x223): undefined reference to mclFreeStackTrace_proxy' libBodyfat.o: In function mlxBodyfatFcn’:
libBodyfat.c:(.text+0x27a): undefined reference to mclFeval_proxy' libBodyfat.o: In function mlfBodyfatFcn’:
libBodyfat.c:(.text+0x2de): undefined reference to `mclMlfFeval_proxy’
collect2: error: ld returned 1 exit status

Hi Mary,

calling a C from Fortran is not a big issue per-se. However with your MATLAB generated routines there are other aspects which make things complicated.

  1. You will need to install the MATLAB Runtime Library - a standalone shared library of 3.9 GB (the 64-bit Linux version).
  2. To link your generated MATLAB C functions, it’s recommended to use mbuild, MATLAB’s C and C++ compiler and linker wrapper. This tool is aware of the MATLAB runtime path and settings. With your Fortran main program you will be on your own.
  3. The MATLAB runtime is stateful, it has to be initialized and terminated appropriately. In Fortan this would look like this:
program main

use, intrinsic :: iso_c_binding

! MATLAB C Library (C function interfaces)
use mcl, only: &
  mclInitializeApplication, &
  mclRunMain, &
  mclTerminateApplication

! Generated library YYY (C function interfaces)
use libYYY, only: &
  libYYYInitialize, libYYYTerminate, &
  mlfBodyfatFcn

implicit none

logical(c_bool) :: success
integer(c_int) :: stat

success = mclInitializeApplication(c_null_ptr, 0)
if (.not. success) then
   write(*,'(A)') "Error: Initialization failed."
   stop 1
end if

! ... main stuff goes here ...

success = mclTerminateApplication()
if (.not. success) then
   write(*,'(A)') "Error: termination failed"
end if
end program
  1. The shared library generated by MATLAB is stateful, it has it’s own initialization and termination routines (libBodyfatInitialize/libBodyfatTerminate). Each shared library you export will have it’s own. Your program will be like an onion of setup/teardown calls.
  2. Finally, everything is initialized… but it’s not time to celebrate yet - we need to create some mxArray instances. You can choose between the C Matrix API or the (old-fashioned) Fortran counterpart that requires a preprocessor and is probably bound to the MATLAB-provided compilers. Both API’s require a non-negligible amount of setup and pointer manipulation to fill the mxArray or retrieve values out of it. I would probably pick the C version.
  3. Now that the MATLAB mxArrays are ready, the generated function can be called. How? Either you write an explicit C interface for the generated function (the ones prepended with mlx and mlf) or you write a C wrapper with name-mangling matching your Fortran compiler (e.g. mlfBodyfatFcn_( /* ... */ ) ). You should probably only be using the MATLAB supported compilers with the generated functions, so heck why not.
  4. Now you are ready to call your function. nargout is the number of outputs you want (Y, Xf, and Af are output arguments). X is your input. I suspect that _U4b and _U4x are cell arrays for some neural-network parameters. Consult the MATLAB documentation for an explanation.
  5. If everything so far has worked, you will get the Y values that you can now reuse in your Fortran program. Hooray!

Personally, before settling on this plan I would investigate exporting the network to some other format. MATLAB provides exportONNXNetwork (maybe join forces with this other thread) and exportNetworkToTensorFlow. If you save the network in HDF5 format you may be able to import it into neural-fortran. (one caveat is the architecture you are dealing with might not be supported).

2 Likes

Thanks a lot Ivan for your thorough explanation. I am going to study it carefully and I come back to you if I fail again. For your last point, the feedforwardnet that I use is of shallow type of network and ONNX supports only the deep networks. So, I cannot export using ONNX.

If the input and output arguments are just plain matrices of doubles, you only need interface for the following routines:

public :: mxCreateDoubleMatrix
public :: mxDestroyArray

public :: mxGetM, mxGetN
public :: mxGetDoubles

! enum mxComplexity
!
enum, bind(c)
   enumerator :: mxREAL = 0
   enumerator :: mxCOMPLEX
end enum

interface
   function mxCreateDoubleMatrix(m,n,ComplexFlag) bind(c,name="mxCreateDoubleMatrix")
      import mwSize, c_int, c_ptr
      integer(mwSize), intent(in), value :: m, n
      integer(c_int), intent(in) :: ComplexFlag
      type(c_ptr) :: mxCreateDoubleMatrix
   end function

   ! ... remaining interfaces

end interface

If they are cell-arrays it’s not going to be pretty in Fortran.

For the runtime initialization

interface
   !> Set up application state shared by all MATLAB Runtime 
   !> instances created in current process
   !>
   function mclInitializeApplication(options, count) bind(c,name="mclInitializeApplication")
      import c_bool, c_int, c_ptr
      type(c_ptr), intent(in) :: options
      integer(c_int), intent(in), value :: count
      logical(c_bool) :: mclInitializeApplication
   end function

   !> Close MATLAB Runtime-internal application state
   !>
   function mclTerminateApplication() bind(c,name="mclTerminateApplication")
      import c_bool
      logical(c_bool) :: mclTerminateApplication
   end function
end interface

Similar interface are needed for the exported library (libYYY).

Depending on your circumstances you should consider if learning to use the C or C++ API directly would be a better investment of time. (No time is lost on wrappers, you can get to work directly. MATLAB compiler and linker wrappers take care of the rest.) In this scenario you would call any Fortran code (in addition to the MATLAB generated C code) from a C or C++ main program.

Thinking about this, it would be much easier to just pass the neural network as a callback into the Fortran main procedure:

#include "matrix.h"
#include "libBodyfat.h"

// Prototype of the main program implemented in Fortran
// It accepts a neural network as callback function. Adapt the 
// call arguments to suit your needs.
void fortran_main( /* ... */ , void (*F)(double *, const double *) );

// This procedure implements the interface F and will be passed 
// as a callback to the Fortran program
//
// It incurs a few unnecessary copies and extra work with creation
// and destruction of the MATLAB arrays. In principle those efforts
// could be spared with a different interface.
// 
static void netF(double *fY, const double *fX) {

    mxArray *X; // an 8 by 4 input matrix
    mxArray *Y; // output matrix of known dimensions

    X = mxCreateDoubleMatrix(8,4,mxREAL);
    memcpy(mxGetDoubles(X),fX,32*sizeof(double));

    // call the trained neural network function
    // optional arguments are set to NULL
    mlfBodyfitFcn(1,&Y,NULL,NULL,X,NULL,NULL);

    int m = mxGetM(Y);
    int n = mxGetN(Y);

    memcpy(mxGetDoubles(Y),fY,m*n*sizeof(double));

    mxDestroyArray(X);
    mxDestroyArray(Y);

}


int main(void) {

  if(!mclInitializeApplication(NULL,0)) {
     printf("%s\n", "Initialization of MATLAB runtime failed");
     return -1;
  }

  if(!libYYYInitialize()) {
     printf("%s\n", "Initialization of libYYY failed");
     return -2;
  }

  // Call Fortran main procedure passing the neural network
  // as a callback function

  fortran_main( /* ... */ , &netF);

  libYYYTerminate();
  mclTerminateApplication();
  
  return 0;

}