public inbox for fortran@gcc.gnu.org
 help / color / mirror / Atom feed
* bad interaction between allocatable arrays and bind(C) subroutine with dimension(..) parameter
@ 2019-08-20 20:32 Gilles Gouaillardet
  2019-10-01  4:15 ` Gilles Gouaillardet
  2020-09-13  7:27 ` bad interaction between lbound/ubound, " Gilles Gouaillardet
  0 siblings, 2 replies; 4+ messages in thread
From: Gilles Gouaillardet @ 2019-08-20 20:32 UTC (permalink / raw)
  To: fortran

[-- Attachment #1: Type: text/plain, Size: 980 bytes --]

Folks,


The attached program evidences an issue when an allocatable array is 
passed to

a bind(C) subroutine that takes a type(*), dimension(..) argument.


The expected output is :

OK: allocatable

OK: static

but with gcc 9.1.0, 9.2.0 and the latest master, the output is :

KO: allocatable

OK: static


Note the test is successful if the argument is declared as type(*), 
dimension(*).


Incidentally, I also noted that if the test program is compiled with -g 
-O0 and ran under gdb (I tried 7.6.1-110.el7 provided by CentOS 7),

the type of 'buf' as reported by the gdb whatis command changes after 
the call to the bind(C) subroutine

22        CALL dummy (buf)
(gdb) whatis buf
type = integer(kind=4) (1)
(gdb) n
23        after = LOC(buf(1))
(gdb) whatis buf
type = integer(kind=4) (0:0)


FWIW, the test is successful with Intel compilers (I tried 2018.3 and 
2019.3)


Could you please investigate this issue ?


Cheers,


Gilles


[-- Attachment #2: test.f90 --]
[-- Type: text/plain, Size: 748 bytes --]

MODULE FOO
INTERFACE
SUBROUTINE dummy(buf) BIND(C, name="sync")
type(*), dimension(..) :: buf
END SUBROUTINE
END INTERFACE
END MODULE

PROGRAM main
    USE FOO
    IMPLICIT NONE
    integer*8 :: before, after

    INTEGER, parameter :: n = 1

    INTEGER, ALLOCATABLE :: buf(:)
    INTEGER :: buf2(n)
    INTEGER :: i

    ALLOCATE(buf(n))
    before = LOC(buf(1))
    CALL dummy (buf)
    after = LOC(buf(1))

    if (before .EQ. after) then
        write (*,*) 'OK: allocatable'
    else
        write (*,*) 'KO: allocatable'
    endif

    
    before = LOC(buf2(1))
    CALL dummy (buf)
    after = LOC(buf2(1))

    if (before .EQ. after) then
        write (*,*) 'OK: static'
    else
        write (*,*) 'KO: static'
    endif


END PROGRAM

^ permalink raw reply	[flat|nested] 4+ messages in thread

* Re: bad interaction between allocatable arrays and bind(C) subroutine with dimension(..) parameter
  2019-08-20 20:32 bad interaction between allocatable arrays and bind(C) subroutine with dimension(..) parameter Gilles Gouaillardet
@ 2019-10-01  4:15 ` Gilles Gouaillardet
  2019-10-01 18:16   ` Paul Richard Thomas
  2020-09-13  7:27 ` bad interaction between lbound/ubound, " Gilles Gouaillardet
  1 sibling, 1 reply; 4+ messages in thread
From: Gilles Gouaillardet @ 2019-10-01  4:15 UTC (permalink / raw)
  To: fortran

Hi Paul,


did you have any chance to investigate the issue I previously reported?


I would like to emphasize the test program I attached (that involves the 
LOC() intrinsic) is a toy program

whose sole purpose is to evidence the issue.


I will be happy to provide a more close to real-life program if needed.

FWIW, I initially found this issue when testing MPI Fortran 2008 
bindings with the TS interface

(long story short, the allocatable array becomes invalid after it is 
passed as a parameter

to a MPI subroutine).


Cheers,


Gilles

On 8/20/2019 4:19 PM, Gilles Gouaillardet wrote:
> Folks,
>
>
> The attached program evidences an issue when an allocatable array is 
> passed to
>
> a bind(C) subroutine that takes a type(*), dimension(..) argument.
>
>
> The expected output is :
>
> OK: allocatable
>
> OK: static
>
> but with gcc 9.1.0, 9.2.0 and the latest master, the output is :
>
> KO: allocatable
>
> OK: static
>
>
> Note the test is successful if the argument is declared as type(*), 
> dimension(*).
>
>
> Incidentally, I also noted that if the test program is compiled with 
> -g -O0 and ran under gdb (I tried 7.6.1-110.el7 provided by CentOS 7),
>
> the type of 'buf' as reported by the gdb whatis command changes after 
> the call to the bind(C) subroutine
>
> 22        CALL dummy (buf)
> (gdb) whatis buf
> type = integer(kind=4) (1)
> (gdb) n
> 23        after = LOC(buf(1))
> (gdb) whatis buf
> type = integer(kind=4) (0:0)
>
>
> FWIW, the test is successful with Intel compilers (I tried 2018.3 and 
> 2019.3)
>
>
> Could you please investigate this issue ?
>
>
> Cheers,
>
>
> Gilles
>

^ permalink raw reply	[flat|nested] 4+ messages in thread

* Re: bad interaction between allocatable arrays and bind(C) subroutine with dimension(..) parameter
  2019-10-01  4:15 ` Gilles Gouaillardet
@ 2019-10-01 18:16   ` Paul Richard Thomas
  0 siblings, 0 replies; 4+ messages in thread
From: Paul Richard Thomas @ 2019-10-01 18:16 UTC (permalink / raw)
  To: Gilles Gouaillardet; +Cc: fortran

Hi Gilles,

Something has gone wrong with the bounds. Before the call, lbound(buf)
is 1 and after it is 0.

I'll take a look.

Cheers

Paul

On Tue, 1 Oct 2019 at 05:15, Gilles Gouaillardet <gilles@rist.or.jp> wrote:
>
> Hi Paul,
>
>
> did you have any chance to investigate the issue I previously reported?
>
>
> I would like to emphasize the test program I attached (that involves the
> LOC() intrinsic) is a toy program
>
> whose sole purpose is to evidence the issue.
>
>
> I will be happy to provide a more close to real-life program if needed.
>
> FWIW, I initially found this issue when testing MPI Fortran 2008
> bindings with the TS interface
>
> (long story short, the allocatable array becomes invalid after it is
> passed as a parameter
>
> to a MPI subroutine).
>
>
> Cheers,
>
>
> Gilles
>
> On 8/20/2019 4:19 PM, Gilles Gouaillardet wrote:
> > Folks,
> >
> >
> > The attached program evidences an issue when an allocatable array is
> > passed to
> >
> > a bind(C) subroutine that takes a type(*), dimension(..) argument.
> >
> >
> > The expected output is :
> >
> > OK: allocatable
> >
> > OK: static
> >
> > but with gcc 9.1.0, 9.2.0 and the latest master, the output is :
> >
> > KO: allocatable
> >
> > OK: static
> >
> >
> > Note the test is successful if the argument is declared as type(*),
> > dimension(*).
> >
> >
> > Incidentally, I also noted that if the test program is compiled with
> > -g -O0 and ran under gdb (I tried 7.6.1-110.el7 provided by CentOS 7),
> >
> > the type of 'buf' as reported by the gdb whatis command changes after
> > the call to the bind(C) subroutine
> >
> > 22        CALL dummy (buf)
> > (gdb) whatis buf
> > type = integer(kind=4) (1)
> > (gdb) n
> > 23        after = LOC(buf(1))
> > (gdb) whatis buf
> > type = integer(kind=4) (0:0)
> >
> >
> > FWIW, the test is successful with Intel compilers (I tried 2018.3 and
> > 2019.3)
> >
> >
> > Could you please investigate this issue ?
> >
> >
> > Cheers,
> >
> >
> > Gilles
> >



-- 
"If you can't explain it simply, you don't understand it well enough"
- Albert Einstein

^ permalink raw reply	[flat|nested] 4+ messages in thread

* bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
  2019-08-20 20:32 bad interaction between allocatable arrays and bind(C) subroutine with dimension(..) parameter Gilles Gouaillardet
  2019-10-01  4:15 ` Gilles Gouaillardet
@ 2020-09-13  7:27 ` Gilles Gouaillardet
  1 sibling, 0 replies; 4+ messages in thread
From: Gilles Gouaillardet @ 2020-09-13  7:27 UTC (permalink / raw)
  To: Paul Richard Thomas; +Cc: fortran

[-- Attachment #1: Type: text/plain, Size: 2317 bytes --]

Hi Paul,


Here is attached a reproducer (bounds.f90) that evidences an issue with 
allocatable arrays :

lbound() and ubound() of an allocatable array return different values 
before and after a Fortran subroutine with dimension(..) parameter (that 
in turns invokes a bind(C) subroutine) is invoked.

Note that if the main program directly CALL dummyc(buf) (instead of 
dummy(buf)), then the error does not occur


FWIW, I tried gcc 9.2.0, gcc 10.2.0 and the latest master branch, and 
they all fail.

The same test passes with Intel ifort.


The issue was initially reported at 
https://stackoverflow.com/questions/63824065/lbound-of-an-array-changes-after-call-to-mpi-gatherv-when-using-mpi-f08-module,

and it turned out MPICH is out of the picture.


I remember I reported a while ago a kind of similar issue with LOC() 
returning different values before and after a subroutine is invoked (see 
the inline email below).

That issue has aleady been fixed, and I have no reason the believe these 
two issues are related.



Could you please investigate this?


Cheers,

Gilles

-------- Forwarded Message --------
Subject: 	bad interaction between allocatable arrays and bind(C) 
subroutine with dimension(..) parameter
Date: 	Tue, 20 Aug 2019 16:19:05 +0900
From: 	Gilles Gouaillardet <gilles@rist.or.jp>
To: 	fortran@gcc.gnu.org <fortran@gcc.gnu.org>



Folks,


The attached program evidences an issue when an allocatable array is 
passed to

a bind(C) subroutine that takes a type(*), dimension(..) argument.


The expected output is :

OK: allocatable

OK: static

but with gcc 9.1.0, 9.2.0 and the latest master, the output is :

KO: allocatable

OK: static


Note the test is successful if the argument is declared as type(*), 
dimension(*).


Incidentally, I also noted that if the test program is compiled with -g 
-O0 and ran under gdb (I tried 7.6.1-110.el7 provided by CentOS 7),

the type of 'buf' as reported by the gdb whatis command changes after 
the call to the bind(C) subroutine

22        CALL dummy (buf)
(gdb) whatis buf
type = integer(kind=4) (1)
(gdb) n
23        after = LOC(buf(1))
(gdb) whatis buf
type = integer(kind=4) (0:0)


FWIW, the test is successful with Intel compilers (I tried 2018.3 and 
2019.3)


Could you please investigate this issue ?


Cheers,


Gilles



[-- Attachment #2: test.f90 --]
[-- Type: text/plain, Size: 748 bytes --]

MODULE FOO
INTERFACE
SUBROUTINE dummy(buf) BIND(C, name="sync")
type(*), dimension(..) :: buf
END SUBROUTINE
END INTERFACE
END MODULE

PROGRAM main
    USE FOO
    IMPLICIT NONE
    integer*8 :: before, after

    INTEGER, parameter :: n = 1

    INTEGER, ALLOCATABLE :: buf(:)
    INTEGER :: buf2(n)
    INTEGER :: i

    ALLOCATE(buf(n))
    before = LOC(buf(1))
    CALL dummy (buf)
    after = LOC(buf(1))

    if (before .EQ. after) then
        write (*,*) 'OK: allocatable'
    else
        write (*,*) 'KO: allocatable'
    endif

    
    before = LOC(buf2(1))
    CALL dummy (buf)
    after = LOC(buf2(1))

    if (before .EQ. after) then
        write (*,*) 'OK: static'
    else
        write (*,*) 'KO: static'
    endif


END PROGRAM

[-- Attachment #3: bounds.f90 --]
[-- Type: text/plain, Size: 893 bytes --]

MODULE FOO
INTERFACE
SUBROUTINE dummyc(x0) BIND(C, name="sync")
type(*), dimension(..) :: x0
END SUBROUTINE
END INTERFACE
contains
SUBROUTINE dummy(x0)
type(*), dimension(..) :: x0
call dummyc(x0)
END SUBROUTINE
END MODULE

PROGRAM main
    USE FOO
    IMPLICIT NONE
    integer :: before(2), after(2)

    INTEGER, parameter :: n = 1

    DOUBLE PRECISION, ALLOCATABLE :: buf(:)
    DOUBLE PRECISION :: buf2(n)

    ALLOCATE(buf(n))
    before(1) = LBOUND(buf,1)
    before(2) = UBOUND(buf,1)
    CALL dummy (buf)
    after(1) = LBOUND(buf,1)
    after(2) = UBOUND(buf,1)

    if (before(1) .NE. after(1)) stop 1
    if (before(2) .NE. after(2)) stop 2

    before(1) = LBOUND(buf2,1)
    before(2) = UBOUND(buf2,1)
    CALL dummy (buf2)
    after(1) = LBOUND(buf2,1)
    after(2) = LBOUND(buf2,1)

    if (before(1) .NE. after(1)) stop 3
    if (before(2) .NE. after(2)) stop 4

END PROGRAM

^ permalink raw reply	[flat|nested] 4+ messages in thread

end of thread, other threads:[~2020-09-13  7:27 UTC | newest]

Thread overview: 4+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2019-08-20 20:32 bad interaction between allocatable arrays and bind(C) subroutine with dimension(..) parameter Gilles Gouaillardet
2019-10-01  4:15 ` Gilles Gouaillardet
2019-10-01 18:16   ` Paul Richard Thomas
2020-09-13  7:27 ` bad interaction between lbound/ubound, " Gilles Gouaillardet

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).