C pointer not nullified using Intel oneAPI Fortran

Greetings,

I’ve tripped over a strange issue while testing my SQLite 3 bindings with Intel oneAPI 2024. It boils down to not being able to nullify C pointers. For instance, an SQLite database handle is freed by calling sqlite3_close(ptr). The C pointer ptr is passed by value, as SQLite expects sqlite3 *db. The pointer itself is therefore never set to NULL by SQLite 3:

    ! int sqlite3_close(sqlite3 *db)
    function sqlite3_close_(db) bind(c, name='sqlite3_close')
        import :: c_int, c_ptr
        implicit none
        type(c_ptr), intent(in), value :: db
        integer(kind=c_int)            :: sqlite3_close_
    end function sqlite3_close_

The interface library provides a wrapper which nullifies the pointer after calling the SQLite function:

    function sqlite3_close(db)
        type(c_ptr), intent(inout) :: db
        integer                    :: sqlite3_close

        sqlite3_close = sqlite3_close_(db)
        if (sqlite3_close == SQLITE_OK) db = c_null_ptr
    end function sqlite3_close

This works as expected with GNU Fortran 13. But compiling the test program using Intel oneAPI Fortran, ptr is never nullified:

    ! The wrapper function sets `ptr` to `c_null_ptr` after
    ! calling interface `sqlite3_close_(ptr)`:
    rc = sqlite3_close(ptr)

    ! Output:
    ! "F" - GNU Fortran
    ! "T" - Intel oneAPI Fortran
    print *, c_associated(ptr)

The same behaviour can be observed when calling the interface directly:

    ! Pass `ptr` by value to SQLite, then nullify:
    rc = sqlite3_close_(ptr)
    ptr = c_null_ptr

    ! Output:
    ! "F" - GNU Fortran
    ! "T" - Intel oneAPI Fortran
    print *, c_associated(ptr)

Does anybody know the reason for this?

1 Like

It looks like maybe one extra instruction found it’s way in that should not be there (?):

If we look at the gfortran output (essentially identical to ifort and flang):

test_:
        push    rbx                    ; push existing rbx value to stack
        mov     rbx, rdi               ; copy the reference to ptr to rbx
        mov     rdi, QWORD PTR [rdi]   ; copy the value pointed to into rdi
        call    sqlite3_close_         ; call sqlite routine with value in rdi
        mov     QWORD PTR [rbx], 0     ; set ptr to NULL
        pop     rbx                    ; restore the old value of rbx
        ret

But with ifx, there appears to be a superfluous instruction.

test_:
        push    rbx
        mov     rbx, rdi
        mov     rdi, qword ptr [rdi]
        call    sqlite3_close_@PLT
        mov     rax, qword ptr [rip + iso_c_binding_mp_c_null_ptr_@GOTPCREL]
        mov     rax, qword ptr [rax]                    ; <----- ???
        mov     qword ptr [rbx], rax
        pop     rbx
        ret
1 Like

Thanks, now, what hath Intel wrought?

Is ptr a dummy argument?

I have the feeling like the address of an argument, and the pointer that argument contains, are getting mixed-up some how?

This program does not reproduce the behavior you describe (I used -fno-inline with ifx to prevent inlining from interfering) :

function sqlite3_close_(ptr) bind(c)
    use, intrinsic :: iso_c_binding
    type(c_ptr), value :: ptr
    integer(c_int) :: sqlite3_close_
    sqlite3_close_ = 0
    if (c_associated(ptr)) then
        print *, "Closing database"
    end if
end function

program main
use, intrinsic :: iso_c_binding
implicit none

integer, target :: a = 42
type(c_ptr) :: p_a

p_a = c_loc(a)

call test(p_a)

print *, c_associated(p_a)

contains

subroutine test(ptr)
    use, intrinsic :: iso_c_binding
    implicit none
    type(c_ptr), intent(inout) :: ptr

    interface
        function sqlite3_close_(ptr) bind(c)
            import c_ptr, c_int
            type(c_ptr), value :: ptr
            integer(c_int) :: sqlite3_close_
        end function
    end interface
    integer(c_int) :: rc

    ! Pass `ptr` by value to SQLite, then nullify:
    rc = sqlite3_close_(ptr)
    ptr = c_null_ptr

end subroutine

The pointer ptr may be a dummy argument, but hasn’t to. A minimal example:

$ cd /tmp/
$ git clone --depth 1 https://github.com/interkosmos/fortran-sqlite3
$ cd fortran-sqlite3/
$ touch demo.f90

The example program demo.f90:

! demo.f90
program main
    use, intrinsic :: iso_c_binding
    use :: sqlite3
    implicit none

    character(len=*), parameter :: DB   = ':memory:'
    integer,          parameter :: FLAG = ior(SQLITE_OPEN_CREATE, SQLITE_OPEN_READWRITE)

    integer     :: rc
    type(c_ptr) :: ptr, stmt

    ptr  = c_null_ptr
    stmt = c_null_ptr

    print '("ptr.....: ", L)',  c_associated(ptr)
    print '("stmt....: ", L)',  c_associated(stmt)

    rc = sqlite3_open_v2(DB, ptr, FLAG)
    print '("open....: ", L)',  c_associated(ptr)

    rc = sqlite3_prepare_v2(ptr, 'SELECT sqlite_version()', stmt)
    print '("prepare.: ", L)',  c_associated(stmt)

    rc = sqlite3_finalize(stmt)
    print '("finalize: ", L)',  c_associated(stmt)

    rc = sqlite3_close(ptr)
    print '("close...: ", L)',  c_associated(ptr)
end program main

Building with GCC:

$ make
$ gfortran -o demo demo.f90 libfortran-sqlite3.a -lsqlite3
$ ./demo
ptr.....: F
stmt....: F
open....: T
prepare.: T
finalize: F
close...: F

Building with Intel oneAPI:

$ make clean
$ make CC=icx FC=ifx
$ ifx -o demo demo.f90 libfortran-sqlite3.a -lsqlite3
$ ./demo
ptr.....:  F
stmt....:  F
open....:  T
prepare.:  T
finalize:  T
close...:  T

The issue can be seen for stmt with sqlite3_finalize() as well.

Does rc always return status ok? :thinking:

Yes. But SQLite is quite generous, so, it doesn’t mean much.

Well it means this part was effectively ignored by ifx, without any doubt on the predicate value. (What you already said.)

I‘m starting to think that this is some kind of protection by Intel against memory leaks. Maybe there is a compiler flag to disable it?

For the subroutine,

subroutine test(ptr)
    use, intrinsic :: iso_c_binding
    type(c_ptr), intent(inout) :: ptr

    interface
        function sqlite3_close_(ptr) bind(c)
            import c_ptr, c_int
            type(c_ptr), value :: ptr
            integer(c_int) :: sqlite3_close_
        end function
    end interface
    integer(c_int) :: rc

    ! Pass `ptr` by value to SQLite, then nullify:
    rc = sqlite3_close_(ptr)
    ptr = c_null_ptr

end subroutine

the ifx compiler (ifx -O2) generates instructions which resemble the following C code:

// test.c
#include <stdint.h>
#define NULL 0

// --- sqlite3 ---

struct sqlite3_database {
    // ...
};

typedef struct sqlite3_database* sqlite3; // opaque pointer

extern int sqlite3_close(sqlite3 *db);

// --- iso_c_binding ---

typedef void * c_ptr;

struct {
    const intptr_t c_null_ptr;
} iso_c_binding = { NULL };

// --- x86-64 ---

static intptr_t a, b, c, d; // registers

static struct {
   // ...
} stack;

#define pop(s) /* ... */
#define push(s) /* ... */

void test_(c_ptr *ptr) {
        
    push(b);                               // push    rbx
    b = (intptr_t) ptr;                    // mov     rbx, rdi
    d = (intptr_t) *ptr;                   // mov     rdi, qword ptr [rdi]
    a = sqlite3_close((sqlite3 *) d);      // call    sqlite3_close_@PLT
    a = iso_c_binding.c_null_ptr;          // mov     rax, qword ptr [rip + iso_c_binding_mp_c_null_ptr_@GOTPCREL]
    a =  *((intptr_t *) a);          // (???) mov     rax, qword ptr [rax] (???)
    *((intptr_t *) b) = a;                 // mov     qword ptr [rbx], rax
    pop(b);                                // pop     rbx
                                           // ret
}

When I compile this with icx -O2, I get

test_:                                  # 
        push    rax
        mov     qword ptr [rip + b], rdi
        mov     rdi, qword ptr [rdi]
        call    sqlite3_close
        mov     rax, qword ptr [rip + iso_c_binding]
        mov     rax, qword ptr [rax]
        mov     rcx, qword ptr [rip + b]
        mov     qword ptr [rcx], rax
        pop     rax
        ret
iso_c_binding:
        .zero   8

which you can see closely reproduces the ifx output of the Fortran routine:

test_:
        push    rbx
        mov     rbx, rdi
        mov     rdi, qword ptr [rdi]
        call    sqlite3_close_@PLT
        mov     rax, qword ptr [rip + iso_c_binding_mp_c_null_ptr_@GOTPCREL]
        mov     rax, qword ptr [rax]
        mov     qword ptr [rbx], rax
        pop     rbx
        ret

In my eyes at least, the following assignment

    a =  *((intptr_t *) a);          // (???) mov     rax, qword ptr [rax] (???)

is superfluous as the register a already contains the null pointer value. To me this smells like a bug.


Try printing the value of transfer(ptr,1_c_intptr_t) before and after the sqlite3_close function call. I expect the value will be different (which would indicate that this is indeed a bug).

Why would that make no sense? Because in your wrapper,

    function sqlite3_close(db)
        type(c_ptr), intent(inout) :: db
        integer                    :: sqlite3_close
        sqlite3_close = sqlite3_close_(db)
        if (sqlite3_close == SQLITE_OK) db = c_null_ptr
    end function sqlite3_close

the C procedure takes the argument by value, meaning it can’t change. If the association status is true, before and after the call, and yet the value pointed to by db changed before and after, it means there was an illegal change.

Probably, a bug in ifx, at some point c_null_ptr is not really NULL as it must be.

There is a work around:
instead of using c_null_ptr to nullify c_ptr variables like

stmt = c_null_ptr

you can do as follows:

real(8), pointer:: a=>null()
stmt = c_loc(a)

I just tested your program using a slightly older version of ifx (ifx (IFORT) 2022.0.0 20211123), despite recommendations from Intel to upgrade to the latest version (2024.x). The operating system is Ubuntu 20.04.6 LTS.

It seems to works correctly:

/tmp/fortran-sqlite3$ make CC=icx FC=ifx
icx -O2 -march=native -c src/sqlite3_macro.c
ifx -O2 -march=native -c src/sqlite3_util.f90
ifx -O2 -march=native -DSQLITE_ENABLE_COLUMN_METADATA=0 -c src/sqlite3.F90
ar rcs libfortran-sqlite3.a sqlite3.o sqlite3_macro.o sqlite3_util.o
/tmp/fortran-sqlite3$ ifx -o demo demo.f90 libfortran-sqlite3.a -lsqlite3
/tmp/fortran-sqlite3$ ./demo 
ptr.....:  F
stmt....:  F
open....:  T
prepare.:  T
finalize:  F
close...:  F

I did however get an error at link time,

$ ifx -o demo demo.f90 libfortran-sqlite3.a -lsqlite3
ld: libfortran-sqlite3.a(sqlite3.o): in function `sqlite3_mp_sqlite3_db_name_':
ifxpk2X4h.i90:(.text+0x2f0): undefined reference to `sqlite3_db_name'

so I temporarily commented out this particular function (it was unused anyways). By the looks of it, the SQLite library I installed is missing this particular function.

Looking at the output of compiler explorer, with ifx v2022, the superfluous instruction is not there :warning: (scroll sideways to see what I mean):

    ifx 2024.0.0                                                                  | ifx 2022.0.0
  1	test_:                                                                        | test_:
  2	        push    rbx                                                           |         push    rbx
  3	        mov     rbx, rdi                                                      |         mov     rbx, rdi
  4	        mov     rdi, qword ptr [rdi]                                          |         mov     rdi, qword ptr [rdi]
  5	        call    sqlite3_close_@PLT                                            |         call    sqlite3_close_@PLT
  6	        mov     rax, qword ptr [rip + iso_c_binding_mp_c_null_ptr_@GOTPCREL]  |         mov     qword ptr [rbx], 0
  7	        mov     rax, qword ptr [rax]                                          |         pop     rbx
  8	        mov     qword ptr [rbx], rax                                          |         ret
  9	        pop     rbx
 10	        ret

If I edit the end of your demo program like this:

    print *, "before close", transfer(ptr, 1_c_intptr_t)
    rc = sqlite3_close(ptr)
    print '("close...: ", L)',  c_associated(ptr)
    print *, "after close ", transfer(ptr, 1_c_intptr_t)

The output produced is,

 before close              25035960
close...:  F
 after close                      0

@interkosmos, can you show what you get on your system?

The function was introduced in SQLite 3.39.0.

The output is:

ptr.....:  F
stmt....:  F
open....:  T
prepare.:  T
finalize:  T
 before close              38143136
 before close               5648439
close...:  T

The used compiler is ifx 2024.0.0 20231017.

Weirdly, the output stays the same when setting ptr explicitly to c_null_ptr:

    print *, 'before close', transfer(ptr, 1_c_intptr_t)
    rc = sqlite3_close(ptr)
    ptr = c_null_ptr
    print *, 'before close', transfer(ptr, 1_c_intptr_t)
    print '("close...: ", L)',  c_associated(ptr) 

And with ifort:

$ ifort --version
ifort (IFORT) 2021.11.0 20231010
Copyright (C) 1985-2023 Intel Corporation.  All rights reserved.
$ ifort -o demo demo.f90 libfortran-sqlite3.a -lsqlite3
$ ./demo
ptr.....:  F
stmt....:  F
open....:  T
prepare.:  T
finalize:  T
 before close              19629240
 before close               4690047
close...:  T

On the systems I’ve tested, the statement

print *, transfer(c_null_ptr,1_c_intptr_t)

would print 0, matching the POSIX standard behavior of representing C’s NULL as 0. The fact that you don’t see this is proof of a bug IMO.

I suggest reporting it via the Intel Fortran Forum (Intel® Fortran Compiler - Intel Community).

Did you also rebuild the library libfortran-sqlite3.a with ifort?

Yes, with the same outcome.

I’ll try this example with an early build of 2024 Update 1 and our main branch and report back. If it’s still present in Update 1 and main branch I’ll get a bug report entered.

2 Likes

Thank you!

The problem remains with Intel oneAPI 2024.1.