Using external modules in AUTO-07p

Hi community,
I am using the bifurcation analysis software AUTO-07p which runs on Fortran. The progam has its own files and commands and the user interface runs via the MINGW32 terminal. As a user I only have access to .f90 files where Subroutines and Functions are defined and I am trying to load a custom module hydrodynamic_forces_routine there with the “use” command. The file looks like this:

 SUBROUTINE FUNC(NDIM,U,ICP,PAR,IJAC,F,DFDU,DFDP) 
!---------- ---- 
   use hydrodynamic_forces_routine
   IMPLICIT NONE
   INTEGER, INTENT(IN) :: NDIM, IJAC, ICP(*)
   DOUBLE PRECISION, INTENT(IN) :: U(NDIM), PAR(*)
   DOUBLE PRECISION, INTENT(OUT) :: F(NDIM)
   DOUBLE PRECISION, INTENT(INOUT) :: DFDU(NDIM,*), DFDP(NDIM,*)

   DOUBLE PRECISION x,y,z,xp,yp,zp,rl,rmu,dE,dM,rmc,dE3,dM3
   REAL Result_Custom

  Result_Custom=hydro_forcesXY(0.001)
   x  = U(1)        
   y  = U(2) 
   z  = U(3) 
   xp = U(4) 
   yp = U(5)
   zp = U(6)+Result_Custom

Up until now, it only works when the function module which I have defined in the separate file, outputs a scalar value hydro_forcesXY. But when I want it to output an array, it does not work. Is this possible, or should I try to do this in the main file of the program?

Thank you, best regards

Is my understanding here correct - you want function hydro_forces to return an array? This requires an explicit interface to be visible to the caller, but if I assume that the module hydrodynamic_forces_routine contains this function, that should be OK. The sample code you show above assigns the function value to a scalar, and that will not work if the result is an array.

If my understanding is not correct, please give more details and maybe some more code. I am not entirely sure what you mean by “function module” here.

Hi @lanast, I am not really sure if this is what you are asking, but do you want the function hydro_forcesXY(arg) to return either scalar or array depending on the argument? Then you have to define it as elemental. Also the Result_Custom is a real scalar, so you cannot store an array there, as well as in zp.
If this is not what you are asking please provide more info and if possible some code.

@sblionel Yes, I want the function to return 2 or more scalar values at once, as an arraz. You are correct that I assign to zp the array value, thanks for that. But even if I remove it, the line:

Result_Custom=hydro_forcesXY(0.001)

produces an error. Actually, the module contains following simple code:

module hydrodynamic_forces_routine
implicit none
contains

!-----hydro_forcesXY----------------------------------------------------
!
!  Function to compute the hydrodynamic forces in hor. and ver. direction
!
!----------------------------------------------------------------------
FUNCTION hydro_forcesXY(r)
IMPLICIT NONE
REAL :: hydro_forcesXY(2)
REAL, INTENT(IN) :: r
hydro_forcesXY= [+x**2,-x**3]
END FUNCTION hydro_forcesXY

end module

Where I already declare hydro_forcesXY(2) as an array, or am I wrong? Do I have to desclare the variable that receives the array as an array also?

@stavros It does not have to dynamically adapt, I know a priori that it should be e.g. an 2x1 array. So it seems, one must desclare the Result_Custom as an array as well? (zp was intended to receive the first of the two elements). Thanks
Actually the long term goal is to assign 8 values to the function, which will calculate 2 resulting values. These I want to use in my main program.

Yes, you must declare the variable receiving an array as an array.

Alright, I defined the receiving variable Results_Custom as an array. At least the error changes, and it now is:
AUTO> run('r3b')
gfortran -O -c r3b.f90 -o r3b.o
gfortran -O r3b.o -o r3b.exe c:/AUTO/auto/07p\lib\*.o
r3b.o:r3b.f90:(.text+0x6c): undefined reference to '__hydrodynamic_forces_routine_MOD_hydro_forcesXY'
collect2.exe: error: ld returned 1 exit status
AUTO Runtime Error: Error running AUTO
AUTO>

It seems as if now the dimensions are correct, but some additional issue prevents the external module to be called perhaps?

Maybe you forgot to put the new module in the linking process?