public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/97046] New: Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
@ 2020-09-14 15:42 igor.gayday at mu dot edu
  2020-09-14 17:09 ` [Bug fortran/97046] " kargl at gcc dot gnu.org
                   ` (10 more replies)
  0 siblings, 11 replies; 12+ messages in thread
From: igor.gayday at mu dot edu @ 2020-09-14 15:42 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=97046

            Bug ID: 97046
           Summary: Bad interaction between lbound/ubound, allocatable
                    arrays and bind(C) subroutine with dimension(..)
                    parameter
           Product: gcc
           Version: 10.2.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: igor.gayday at mu dot edu
  Target Milestone: ---

Consider the following code:

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

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.

gcc versions 9.2.0, 10.2.0 and the latest master branch are all affected.

In particular, this causes issues with mpi_f08 module, see:
https://stackoverflow.com/questions/63824065/lbound-of-an-array-changes-after-call-to-mpi-gatherv-when-using-mpi-f08-module

This might be a duplicate of Bug #94070.

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

end of thread, other threads:[~2021-10-19 10:25 UTC | newest]

Thread overview: 12+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2020-09-14 15:42 [Bug fortran/97046] New: Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter igor.gayday at mu dot edu
2020-09-14 17:09 ` [Bug fortran/97046] " kargl at gcc dot gnu.org
2020-09-14 23:56 ` gilles.gouaillardet at gmail dot com
2020-09-15  0:25 ` sgk at troutmask dot apl.washington.edu
2020-09-15  1:13 ` gilles.gouaillardet at gmail dot com
2020-09-15  5:56 ` igor.gayday at mu dot edu
2021-05-19 18:09 ` jrfsousa at gcc dot gnu.org
2021-05-30 20:08 ` dominiq at lps dot ens.fr
2021-06-14 23:23 ` jrfsousa at gcc dot gnu.org
2021-06-14 23:24 ` jrfsousa at gcc dot gnu.org
2021-07-26 12:33 ` cvs-commit at gcc dot gnu.org
2021-10-19 10:25 ` burnus at gcc dot gnu.org

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).