Undefined reference to `setup_r1_'

Dear colleagues,
I wrote a short program using rksuite_90.f90 from: ode/rksuite,
name of my program: example_rksuite.f90

I did: gfortran -c rksuite_90.f90 no errors/no warning
gfortran -c example_rksuite.f90 no errors/no warning

       gfortran -g -o example_rksuite  example_rksuite.f90  rksuite_90.f90  :

           I get: undefined reference to `setup_r1_'

     I tried:
      nm rksuite_90.o | grep setup_r1   => __rksuite_90_MOD_setup_r1

I think: my compiler is looking for setup_r1, but cannot find it !?

I was checking up: procedure setup_r1 is part of: rksuite_90.f90:
subroutine setup_r1(comm,t_start,y_start,t_end,tolerance,thresholds, &
method,task,error_assess,h_start,message)

I found: subroutine setup_r1 is part of rksuite_90.o with name
__rksuite_90_MOD_setup_r1

What to do?

Thank you very much for help!
Andreas

The setup_r1 subroutine must be included within module: in the file rksuite_90.f90, you should find module rksuite at the beginning of the file. To use the subroutines, functions, constants, etc., defined within this module, you should add use rksuite (or use rksuite, only: setup_r1) where you want to use this subroutine.

I tried: use rksuite_90, but it still doesn’t work. same error message

rksuite_90.f90 consists of:

module rksuite_90_prec

end module rksuite_90_prec

module rksuite_90

module procedure setup_r1

module procedure range_intergrate_r1

module procedure step_integrate_r1

module procedure statistics_r1

module procdure global_error_r1

module procedure reset_t_end_r1

module procedure interpolate_r1

module procedure set_stop_on_fatal_r1

module procedure get_saved_fatal_r1

module procedure collect_garbage_r1

end module rk_suite_90

Thank you for help!

With gfortran -g -o example_rksuite example_rksuite.f90 rksuite_90.f90, the compiler starts by compiling example_rksuite.f90, and it won’t find the module since it’s not yet compiled.

Try to build in 3 steps, starting with the module file:

gfortran -g -c rksuite_90.f90 -o rksuite_90.o
gfortran -g -c example_rksuite.f90 -o example_rksuite.o
gfortran -o example_rksuite rksuite_90.o example_rksuite.o

After the first step, you should see a rksuite_90.mod file appearing.

I get:
$ gfortran -o example_rksuite rksuite_90.o example_rksuite.o
C:/msys64/ucrt64/bin/…/lib/gcc/x86_64-w64-mingw32/14.2.0/…/…/…/…/x86_64-w64-mingw32/bin/ld.exe:
example_rksuite.o: in function test_rksuite': C:/ode_rksuite/example_rksuite.f90:30:(.text+0x17c): undefined reference to setup_r1_’
collect2.exe: error: ld returned 1 exit status

in main program I have: use rksuite_90

Thank you for help!

Looking at the file rksuite_90.bas:

The routine setup_r1 is part of an interface:

interface setup
   module procedure setup_r1
end interface

The module contains the private statement, meaning that all variables, routines, etc, are private by default, unless explicitly declared as public: only setup is declared as public, not setup_r1, therefore what you have to call is setup rather than setup_r1

thank you very much for answer:

example_rksuite.f90:26:108:

26 | call setup(comm, t_start, y, t_end, tolerance, thresholds, method, task, error_assess, h
_start, message)
|
1
Error: There is no specific subroutine for the generic ā€˜setup’ at (1)

I controlled also type and order of arguments.

Tank for help!
Andreas

All arguments must agree in terms of Type / Kind / Rank (TKR). Without seeing your main code it’s impossible to check…

program test_rksuite
use rksuite_90 ! Use the module
implicit none
!public setup
real(8) :: t, y, yp
real(8) :: t_start, t_end, tolerance, thresholds(1)
integer :: comm, method, task, error_assess
real(8) :: h_start
character(len=100) :: message ! Adjusted message length

! Initialize parameters
comm = 1  ! Initialize comm with an example value
t_start = 0.0d0
t_end = 10.0d0
y = 1.0d0
yp = 0.0d0
tolerance = 1.0d-6
thresholds(1) = 0.0d0
method = 1
task = 1
error_assess = 0
h_start = 0.1d0
message = "Initialization Complete"

! Call the public interface 'setup' instead of 'setup_r1'
call setup_r1(comm,t_start,y_start,t_end,tolerance,thresholds,method,task,error_assess,h_start,message)
print *, 'Endgültiger Wert von y:', tolerance
! Additional computations here

end program test_rksuite

please excuse circumstances!

I wouldn’t say that the arguments agree…

In the routine, comm is declared as type(rk_comm_real_1d), but you are passing an integer; task and method are character(len=*), but you are passing integers; message is a logical, but you are passing a character(len=100)…

And BTW, try sticking with the way the real arguments are declared in the routine. When a dummy argument is:
real(kind=wp), intent(in) :: tolerance
Then declare it in your main with real(kind=wp) instead of real(8). real(8) will most of time work because with the most current compilers wp = selected_real_kind(10,50) will be effectively equal to 8, but this is not guaranteed, as some compilers use a different numbering for the kinds. Also, if at some point you want to change the definition of wp, your code will always be consistent with the routines in rksuite_f90.

I corrected my code, but something still doesn’t work:

program test_rksuite
use rksuite_90 ! Use the module
implicit none

! The precision 'wp' is now inherited from the module 'rksuite_90'
! Define precision

! Variable declarations
real(8):: t_start, t_end       ! indep!
real(8):: tolerance            ! tolerance
real(8):: y_start  ! dep!
real(8), dimension(1) :: thresholds  ! shp-dep!
type(rk_comm_real_1d) :: comm         ! Communication structure
real(8):: h_start              ! indep!
logical :: error_assess, message               ! Logical flag for error assessment
character(len=100) :: method, task    ! Method and task strings

! Initialize parameters
! Assuming 'comm' has a different valid member that should be set
! Adjust this according to the actual members of rk_comm_real_1d
! Example:
! comm%some_member = 1

t_start = 0.0
t_end = 10
y_start = 1.0
thresholds(1) = 0.0
tolerance = 1.0e-6
h_start = 0.1
method = "Method1"
task = "Task1"
error_assess = .true.
message = .true.


! Call the setup routine
call setup_r1(comm, t_start, y_start, t_end, tolerance, thresholds, method, task, error_assess, h_start, message)

! Additional computations here

end program test_rksuite

Thank you for help! Andreas

The name setup_r1 is private. You should see that if you specify it explicitly on the include line:

use rksuite_90, only: setup_r1 ! (error)
use rksuite_90, only: setup    ! expected to work

The error you got previously, i.e.

26 | call setup(comm, t_start, y, t_end, tolerance, thresholds, method, task, error_assess, h
_start, message)
|
1
Error: There is no specific subroutine for the generic ā€˜setup’ at (1)

was because of the type mismatches as @PierU has explained. When explicit interfaces are used, that is you use procedures from a module, the compiler performs strict type-checking (or rather type-, kind- and rank-checking) for all passed arguments. (There are some exceptions where the rules are slightly different, but I don’t want to go into the details here.)

program test_rksuite
use rksuite_90, only: setup, rk_comm_real_1d
implicit none

! The precision 'wp' is now inherited from the module 'rksuite_90'
! Define precision

! Variable declarations
integer, parameter :: wp = selected_real_kind(10,50)

! real(kind=wp), dimension(:), allocatable :: thresholds
real(kind = wp):: t_end, t_start ! indep!
real(kind = wp):: tolerance ! tolerance
real(kind = wp):: y_start ! dep!
! real(kind = wp):: thresholds ! shp-dep!
real(kind=wp), dimension(:), allocatable :: thresholds
type(rk_comm_real_1d) :: comm ! Communication structure

real(kind = wp):: h_start              ! indep!
logical :: error_assess, message               ! Logical flag for error assessment
character(len=100) :: task, method    ! Method and task strings

! Initialize parameters

t_start = 0.0_wp
t_end = 10_wp
y_start = 1.0_wp
allocate(thresholds(1)) 
thresholds(:) = 0.0_wp
tolerance = 1.0e-6
h_start = 0.1
method = "Method1"
task = "Task1"
error_assess = .true.
message = .true.


! Call the setup routine
call setup_r1(comm, t_start, y_start, t_end, tolerance, thresholds, method, task, error_assess, h_start, message)

! Additional computations here

end program test_rksuite

with call setup it doesn’t work at all??? moreover, I think there is some mistake in variable declaration ,maybe according to comm??? Thank you very much for help! Andreas

It’s difficult to help you just with ā€œit doesn’t workā€ā€¦ At the very least copy/paste the error messages you get from the compiler.

That said:

Unless you have declared setup_r1 as public in the rksuite_90 module, this call won’t work as the setup_r1 name is not visible from your code. You have been told in the above comments to replace it by:

! Call the setup routine
call setup(comm, t_start, y_start, t_end, tolerance, thresholds, method, task, error_assess, h_start, message)

Thank you for answer! Yes, you are right: I tried several times, as you told- with: call setup(comm, t_start, y_start, t_end, tolerance, thresholds, method, task, error_assess, h_start, message) but always with same error message: Error: There is no specific subroutine for the generic ā€˜setup’ at (1) ???

(when I tried: gfortran -c example_rksuite.f90 with: call setup_r1 I get no errormessage… ???)

I believe , there is something wrong with: type(rk_comm_real_1d) :: comm
?

Because of this:

 use rksuite_90, only: setup, rk_comm_real_1d

You are importing only setup and rk_comm_real_1d, not setup_r1: consequently the compiler assumes that setup_r1 is an external routine and that its interface is unknown at this point. And because the interface is unknown, the compiler does not check the arguments, hence no reported error.

And BTW you should import wp as well instead of redefining it.

Now I have found the error: y_start should be an array, not a scalar.

1 Like

Both of these variables are declared as real(wp), but the constants on the right are the default real kind. If there is a mismatch of kind values, then this can result in sometimes difficult to debug errors. It would probably be more robust to declare the constants with the appropriate kind, namely 1.0e-6_wp and 0.1_wp.

thanks !!!

thanks to all!!

no errors, because of help from all of you!!!
program test_rksuite
use rksuite_90, only: setup, rk_comm_real_1d
implicit none

! The precision 'wp' is now inherited from the module 'rksuite_90'
! Define precision

! Variable declarations
integer, parameter :: wp = selected_real_kind(10,50)
integer :: errcode  ! Variable zur Erfassung von Allokationsfehlern

real(kind = wp):: t_end, t_start      ! indep!
real(kind = wp):: tolerance            ! tolerance
real(kind = wp), dimension(:), allocatable :: y_start
real(kind=wp), dimension(:), allocatable :: thresholds
type(rk_comm_real_1d) :: comm         ! Communication structure

real(kind = wp):: h_start              ! indep!
logical :: error_assess, message               ! Logical flag for error assessment
character(len=100) :: task, method    ! Method and task strings

! Initialize parameters

t_start = 0.0_wp
t_end = 10_wp
y_start = 1.0_wp
allocate(thresholds(2)) 
thresholds(:) = 0.0_wp
tolerance = 0.01_wp    !1.0e6_wp
h_start = 0.1_wp
method = "Method1"
task = "RTask1"
error_assess = .true.
message = .true.

! Dynamische Arrays allokieren und Fehlerprüfung
if (.not. allocated(y_start)) then
    allocate(y_start(2), stat=errcode)
    if (errcode /= 0) then
        print *, "Fehler bei der Allokation von y_start"
        stop
    end if
end if

if (.not. allocated(thresholds)) then
    allocate(thresholds(2), stat=errcode)
    if (errcode /= 0) then
        print *, "Fehler bei der Allokation von thresholds"
        stop
    end if
end if

! Arrays initialisieren
y_start = [1.0_wp, 2.0_wp]      ! Beispielwerte für y_start
thresholds = [1.0_wp, 2.0_wp]   ! Beispielwerte für thresholds

! Call the setup routine
call setup(comm, t_start, y_start, t_end, tolerance, thresholds, method, task, error_assess, h_start, message)

! Additional computations here
     print *," ", 4

if (allocated(y_start)) then
deallocate(y_start)
end if
if (allocated(thresholds)) then
deallocate(thresholds)
end if

end program test_rksuite

I am retired teacher, studying in the 80s, Fortran is absolutely new for me … Andreas

1 Like