Derived type saving information from interoperable callback function

Hello everyone, first post in the forum (and quite a newbie at Fortran)

I have been working on a fortran project which at some point needs to solve electrical circuits. After some thought, we have decided to try and use NgSpice (Ngspice, the open source Spice circuit simulator - Intro). NgSpice is written in C but can be compiled as a shared library, and used from other applications.

I have been learning how to write an interface to C, but I have (apparently) reached a dead-end and I don’t know whether I might have to change my strategy. I will try to be thorough in my explanation but don’t show more code than is necessary.

The summary is: I have a derived type that calls some of the C shared functions in its procedures. One of these shared functions receives a series of callbacks as arguments. These callbacks contain the information of the simulation (voltages, times, etc), and I can access those values when the callback function is being executed. However, I don’t know how to make that information available to my type.

In more detail: I have a module (ngspice_interface_mod) where the interoperable types and functions are defined. ngSpice_init is a function from the shared library which receives a series of callback functions. There are more shared functions for which bindings have been written. SendStat is one of the callback functions.

module ngspice_interface_mod

    use iso_c_binding
    implicit none

   interface

        integer(c_int) function ngSpice_Init(&
            cbSendChar, cbSendStat, cbControlledExit, cbSendData, &
            cbSendInitData, cbBGThreadRunning, returnPtr) bind(C, name="ngSpice_Init")
            import :: c_int, c_ptr, c_funptr
            type(c_funptr), intent(in), value :: cbSendChar
            type(c_funptr), intent(in), value :: cbSendStat
            type(c_funptr), intent(in), value :: cbControlledExit
            type(c_funptr), intent(in), value :: cbSendData
            type(c_funptr), intent(in), value :: cbSendInitData
            type(c_funptr), intent(in), value :: cbBGThreadRunning
            type(c_ptr), value, intent(in) :: returnPtr
        end function
   end interface

   contains

    integer(c_int) function SendChar(output, id, returnPtr) !bind(C, name="SendChar")
        type(c_ptr), value, intent(in) :: output
        integer(c_int), intent(in), value :: id
        type(c_ptr), value, intent(in) :: returnPtr
        character(len=:), pointer :: f_output
        character(len=:), allocatable :: string
        
        SendChar = 0
        call c_f_pointer(output, f_output)
        string = f_output(1:index(f_output, c_null_char)-1)
        ! string = string(index(string,'stdout'):len(string)) ! remove 'stdout'?
        write(*,*) 'SendChar: ', trim(string)
        if (index('stderror Error:', string) /= 0) then
            SendChar = 1
        end if
    end function
end module

The callback function SendChar arguments have to be those because the callback function needed by the ngSpice_init function in C is typedef int (SendChar)(char*, int, void*)

There is another module (circuit_mod) that defines a type and some type-bound procedures. These are the wrappers around the C functions. Leaving it to the bare-bone minimum, it’s:

module circuit_mod

    use ngspice_interface_mod
    implicit none

    type, public :: circuit_t
    real :: voltage    

    contains
        procedure :: init

    end type circuit_t

contains
   subroutine init(this)
        class(circuit_t) :: this
        type(c_funptr) :: cSendChar
        type(c_funptr) :: cSendStat
        type(c_funptr) :: cControlledExit
        type(c_funptr) :: cSendData
        type(c_funptr) :: cSendInitData
        type(c_funptr) :: cBGThreadRunning
        type(c_ptr) :: returnPtr

        integer :: res
        
        cSendChar = c_funloc(SendChar)
        cSendStat = c_funloc(SendStat)
        cControlledExit = c_funloc(ControlledExit)
        cSendData = c_funloc(SendData)
        cSendInitData = c_funloc(SendInitData)
        cBGThreadRunning = c_funloc(BGThreadRunning)

        res = ngSpice_Init(cSendChar, cSendStat, cControlledExit, cSendData, cSendInitData, cBGThreadRunning, returnPtr)
    end subroutine

where the procedures whose definition is missing (as SendStat) are in the interface module.

Let’s say I want to store a voltage in this%voltage when the SendChar function is called. I could not, because the callback not being bound to the type, it knows nothing about the type.

However, if I try to make SendChar into a type-bound procedure, defining it in circuit_mod (and removing its definition from the ngspice_interface_mod) as:

    integer(c_int) function SendChar(this, output, id, returnPtr)
        class(circuit_t) :: this
        type(c_ptr), value, intent(in), optional :: output
        integer(c_int), intent(in), value, optional :: id
        type(c_ptr), value, intent(in), optional :: returnPtr
        character(len=:), pointer :: f_output
        character(len=:), allocatable :: string
        
        SendChar = 0
        call c_f_pointer(output, f_output)
        string = f_output(1:index(f_output, c_null_char)-1)
        write(*,*) 'SendChar: ', trim(string)
        if (index('stderror Error:', string) /= 0) then
            SendChar = 1
        end if

    end function

the output variable, (which in C would a char*) is null (or I think it0s null, because the fortran pointer f_output is null after calling c_f_pointer.

Long story short: how can my interface capture (and store) anything happening inside the callback functions?

Please let me know which additional information would be useful to properly state the problem. I tried not to get into unnecesary details, but then I might have providing too little information.

Thanks,
Alberto

Welcome to the forum. For a Fortran newbie your question is pretty advanced :slight_smile:. I am sure people will look at it, but for me, I need to digest it a bit.

Just after I left work it came to me that the return pointer is the way to pass the information. i have been working on that today, and I can finally manage the information the way I need. For completion (and because it might be useful for someone else):

In the definition of the binded function ngSpice_Init, the return pointer is changed to

            type(*) :: returnPtr

I define a simple derived type to hold the information of nodes voltages and indices

    type test_t
        real(kind=8), allocatable :: voltages(:)
        real(kind=8), allocatable :: nodeIndices(:)
    end type test_t

which is my derived type circuit_t

   type, public :: circuit_t
    character (len=:), allocatable :: name
    real :: time = 0.0, dt = 0.0
    logical :: errorFlag = .false.
    

    type(test_t) :: values   
   ...

Then, in the call to the ngSpice_Init function, the member values is passed to the return pointer (the last argument)

        res = ngSpice_Init(cSendChar, cSendStat, cControlledExit, cSendData, cSendInitData, cBGThreadRunning, returnPtr)

In the callback functions, the definition of returnPtr is changed accordingly, from:

type(c_ptr), value, intent(in) :: returnPtr

to

type(test_t) :: returnPtr

Now, returnPtr%voltages and returnPtr%nodeIndices can be changed inside the callback functions, and the changes are propagated to the instance of my circuit_t type.

Necessary refactorings and improvements notwithstanding, the core functionality is there :slight_smile:

Hi Alberto, and welcome.
I must first say that I know nothing about NgSpice library you are using.
I did a quick search for the function ngSpice_Init, and stumbled upon the official manual. At page 483, when explaining the arguments of such function, they state:

void* Using the void pointer, you may send the object address of the calling function
(’self’ or ’this’ pointer) to ngspice.dll. This pointer will be returned unmodified by
any callback function (see the *void pointers in Chapt. 19.3.3). Callback functions
are to be defined in the global section of the caller. Because they now have got the
object address of the calling function, they may direct their actions to the calling
object.

I’m not an expert in such things, but from that sentence I understand that the last void * argument accepts the address of the calling object. Which I guess is what I then passed to SendChar(char *, int, void *) as last parameter, so that in your defined implementation, you might access data of the calling object.

So, I guess you could try something like:

res = ngSpice_Init(cSendChar, 
                   cSendStat, 
                   cControlledExit, 
                   cSendData, 
                   cSendInitData, cBGThreadRunning, c_loc(this))

and then, in SendChar implementation, dereference the void pointer, knowing that you passed a reference to a Fortran circuit_t polymorphic type:

integer(c_int) function SendChar(output, id, lastArg) !bind(C, name="SendChar")
   type(c_ptr), value, intent(in) :: output
   integer(c_int), intent(in), value :: id
   type(c_ptr), value, intent(in) :: lastArg

   type(circuit_t), pointer :: caller_obj

   call c_f_pointer(lastArg, caller_obj)
   !  use caller_obj 

But, this might be far from solving your actual problem.

EDIT: typos.

Hi @Alberto , welcome to the forum. Glad you managed to get something working. I would recommend making the modifications as demonstrated by @mEm in order to be more standards conforming. Specifically using c_loc(this) in the call to ngSpice_init and using c_f_pointer(returnPtr, this) in the callbacks. i.e.

subroutine init(this)
        class(circuit_t), pointer :: this
        type(c_funptr) :: cSendChar
        type(c_funptr) :: cSendStat
        type(c_funptr) :: cControlledExit
        type(c_funptr) :: cSendData
        type(c_funptr) :: cSendInitData
        type(c_funptr) :: cBGThreadRunning
        type(c_ptr) :: returnPtr

        integer :: res
        
        cSendChar = c_funloc(SendChar)
        cSendStat = c_funloc(SendStat)
        cControlledExit = c_funloc(ControlledExit)
        cSendData = c_funloc(SendData)
        cSendInitData = c_funloc(SendInitData)
        cBGThreadRunning = c_funloc(BGThreadRunning)

        res = ngSpice_Init(cSendChar, cSendStat, cControlledExit, cSendData, cSendInitData, cBGThreadRunning, c_loc(this))
    end subroutine
    integer(c_int) function SendChar(output, id, returnPtr) !bind(C, name="SendChar")
        type(c_ptr), value, intent(in) :: output
        integer(c_int), intent(in), value :: id
        type(c_ptr), value, intent(in) :: returnPtr
        character(len=:), pointer :: f_output
        character(len=:), allocatable :: string

        type(circuit_t), pointer :: this
        call c_f_pointer(returnPtr, this)
        
        SendChar = 0
        call c_f_pointer(output, f_output)
        string = f_output(1:index(f_output, c_null_char)-1)
        ! string = string(index(string,'stdout'):len(string)) ! remove 'stdout'?
        write(*,*) 'SendChar: ', trim(string)
        if (index('stderror Error:', string) /= 0) then
            SendChar = 1
        end if
    end function

Note that you’ll need to modify the declaration of the this argument to init to add the pointer attribute, add the target attribute to declarations of any type(circuit_t) variables and add the pointer attribute to any other type or class(circuit_t) procedure arguments that are not intent(in) or value. This ensures that any modifications made to that object are made to the actual object in memory at the pointer location given to the C library, and that the pointer location given to the C library is to the real variable, and not any temporary copies.

Dear @everythingfunctional @mEm, thank you for your replies. I’m trying to implement something similar to your suggestions, but the argument to c_loc cannot be polymorphic . To make it work I guess I can change init to not be type-bound and changing the definitions of the functions where corresponding. So far I’m finding segmentation faults when trying this approach, but I think I can make it work. Otherwise, the other option works just fine, even if less standard

@Alberto have you tried making your init function accepting a void * itself?
I.e.:

subroutine init_circuit(this)
        type(c_ptr), value, intent(in) :: this
        type(c_funptr) :: cSendChar
        type(c_funptr) :: cSendStat
        type(c_funptr) :: cControlledExit
        type(c_funptr) :: cSendData
        type(c_funptr) :: cSendInitData
        type(c_funptr) :: cBGThreadRunning
        integer :: res

        ! use this in case you'd need to use/modify your Fortran object within this init function.
        type(circuit_t), pointer :: this_deref
        call c_f_pointer(this, this_deref)
        
        cSendChar = c_funloc(SendChar)
        cSendStat = c_funloc(SendStat)
        cControlledExit = c_funloc(ControlledExit)
        cSendData = c_funloc(SendData)
        cSendInitData = c_funloc(SendInitData)
        cBGThreadRunning = c_funloc(BGThreadRunning)

        res = ngSpice_Init(cSendChar, cSendStat, cControlledExit, cSendData, cSendInitData, cBGThreadRunning, this)
    end subroutine

So that, whenever you will call the init function on a circuit_t object, you’d have something like:

type(circuit_t), target :: a_circuit_object_variable
...
call init_circuit(c_loc(a_circuit_object_variable))

The code for SendChar would remain as in @everythingfunctional 's answer.

PS: if in your circuit_t init function all you do is “preparing” the call to the underlying C companion procedure, I think you can factor out that procedure entirely, by storing the function pointers as static module variables, and so replacing each call to init with directly ngSpice_Init, passing as last argument the address of the calling object:

type(circuit_t), target :: a_circuit_object_variable
integer(c_int) :: res
...
! at init, directly calling the C function (all cSendChar, etc.., module static variables)
res = ngSpice_Init(cSendChar, cSendStat, cControlledExit, cSendData, cSendInitData, cBGThreadRunning, c_loc(a_circuit_object_variable))

Indeed, this makes sense if you call this function several times. Otherwise, keep it like it is.

Hmm, indeed, I hadn’t noticed that. The standard says:

18.2.3.7 C_LOC (X)

Argument. X … shall be … a nonpolymorphic variable …

I’m not sure why that’s there, and you can’t even work around it as you might expect with

function wrapped_c_loc(x)
    type(*), pointer, intent(in) :: x
    type(c_ptr) :: wrapped_c_loc
    wrapped_c_loc = c_loc(x)
end function

because

C714 An assumed-type entity shall be a dummy data object that does not have the ALLOCATABLE, CODIMENSION, INTENT (OUT), POINTER, or VALUE attribute and is not an explicit-shape array.

That said, you could do

select type (this)
type (circuit_t)
  returnPtr = c_loc(this)
end type

or make the init procedure not type-bound and change the argument declaration to

type(circuit_t), pointer :: this

Dear all,

eventually I settled for the option not involving working aroung the polymorphic type, i.e., I just pass a simple derived type containing the information I need, which works just fine.

A different issue has come up. We are developing this project so it will work on different architectures and compilers. When using gcc on linux, the pointer passing from C to Fortran seems to work as expected. However, when using Intel LLVM on linux, the pointers passed to the callback functions in Fortran have wrong values, they seem to be numbers rather than memory positions.

To be clear, I’m referring, for instance, to the output variable in:

    integer(c_int) function SendChar(output, id, nodes)
        type(c_ptr), value, intent(in) :: output

While debugging I can access the .C file from which the call comes, and at that point, the corresponding variable holding a pointer looks fine (as vague at that sounds, but I’m still in the process of debugging).

Do you know of any known problems when interfacing C and Fortran related to the use a particular compiler? I will post in the forums of the C program as well, but I doubt I will clarify anything, since this is the first Fortran interface written for that program.