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

* [Bug fortran/97046] Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
  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 ` kargl at gcc dot gnu.org
  2020-09-14 23:56 ` gilles.gouaillardet at gmail dot com
                   ` (9 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: kargl at gcc dot gnu.org @ 2020-09-14 17:09 UTC (permalink / raw)
  To: gcc-bugs

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

kargl at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |kargl at gcc dot gnu.org

--- Comment #1 from kargl at gcc dot gnu.org ---
(In reply to Igor Gayday from comment #0)
> Consider the following code:
> 
> MODULE FOO
> INTERFACE
> SUBROUTINE dummyc(x0) BIND(C, name="sync")
> type(*), dimension(..) :: x0
> END SUBROUTINE
> END INTERFACE

What are the implementation details for sync?

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

* [Bug fortran/97046] Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
  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
                   ` (8 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: gilles.gouaillardet at gmail dot com @ 2020-09-14 23:56 UTC (permalink / raw)
  To: gcc-bugs

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

Gilles Gouaillardet <gilles.gouaillardet at gmail dot com> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |gilles.gouaillardet at gmail dot c
                   |                            |om

--- Comment #2 from Gilles Gouaillardet <gilles.gouaillardet at gmail dot com> ---
This is the libc subroutine

void sync(void);


The point here is any subroutine (that will not cause a crash) can be used to
evidence the issue.

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

* [Bug fortran/97046] Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
  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
                   ` (7 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2020-09-15  0:25 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from Steve Kargl <sgk at troutmask dot apl.washington.edu> ---
On Mon, Sep 14, 2020 at 11:56:18PM +0000, gilles.gouaillardet at gmail dot com
wrote:
> This is the libc subroutine
> 
> void sync(void);
> 
> The point here is any subroutine (that will not cause a crash) can be used to
> evidence the issue.
> 

Isn't there a mismatch in the number of
arguments provided by your Fortran code
and the parameters expected in sync(2)?

dummy (struct array15_unknown & restrict x0)
{
  {
    void * cfi.0;

    x0->span = (integer(kind=4)) x0->dtype.elem_len;
    x0->dtype.attribute = 2;
    cfi.0 = 0B;
    _gfortran_gfc_desc_to_cfi_desc (&cfi.0, (struct array15_unknown *) x0);
    x0->dtype.attribute = 2;
    dummyc (cfi.0);
    _gfortran_cfi_desc_to_gfc_desc ((struct array15_unknown *) x0, &cfi.0);
    __builtin_free (cfi.0);
  }
}

dummyc(cfi.0) becomes sync(cfi.0).
Is this standard conform?

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

* [Bug fortran/97046] Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
  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
                   ` (2 preceding siblings ...)
  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
                   ` (6 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: gilles.gouaillardet at gmail dot com @ 2020-09-15  1:13 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #4 from Gilles Gouaillardet <gilles.gouaillardet at gmail dot com> ---
I crafted the reproducer based on a previous one that has already been merged,
and using a libc subroutine was not an issue back then.

https://gcc.gnu.org/git?p=gcc.git;a=blob;f=gcc/testsuite/gfortran.dg/ISO_Fortran_binding_14.f90;h=388c5438252d49342f6bd357850062697fafb7b4;hb=980f185ce3ba6d532530ce0f23bfb6e30320fd8a


But I get your point, and you can

SUBROUTINE dummyc(x0) BIND(C, name="dummyc")

and then in dummyc.c

#include "ISO_Fortran_binding.h"

void dummyc (CFI_cdesc_t * x){
}



This does not change the fact that the test fails with GNU compilers though.

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

* [Bug fortran/97046] Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
  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
                   ` (3 preceding siblings ...)
  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
                   ` (5 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: igor.gayday at mu dot edu @ 2020-09-15  5:56 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from Igor Gayday <igor.gayday at mu dot edu> ---
I'd like to add that Gilles Gouaillardet is the author of the reproducer in my
original post.

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

* [Bug fortran/97046] Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
  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
                   ` (4 preceding siblings ...)
  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
                   ` (4 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: jrfsousa at gcc dot gnu.org @ 2021-05-19 18:09 UTC (permalink / raw)
  To: gcc-bugs

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

José Rui Faustino de Sousa <jrfsousa at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |jrfsousa at gcc dot gnu.org

--- Comment #6 from José Rui Faustino de Sousa <jrfsousa at gcc dot gnu.org> ---
Patch posted:

https://gcc.gnu.org/pipermail/fortran/2021-May/056054.html

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

* [Bug fortran/97046] Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
  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
                   ` (5 preceding siblings ...)
  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
                   ` (3 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: dominiq at lps dot ens.fr @ 2021-05-30 20:08 UTC (permalink / raw)
  To: gcc-bugs

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

Dominique d'Humieres <dominiq at lps dot ens.fr> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
     Ever confirmed|0                           |1
   Last reconfirmed|                            |2021-05-30
             Status|UNCONFIRMED                 |ASSIGNED

--- Comment #7 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
> Patch posted:
>
> https://gcc.gnu.org/pipermail/fortran/2021-May/056054.html


The patch fixes this PR, see also pr94331.

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

* [Bug fortran/97046] Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
  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
                   ` (6 preceding siblings ...)
  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
                   ` (2 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: jrfsousa at gcc dot gnu.org @ 2021-06-14 23:23 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #8 from José Rui Faustino de Sousa <jrfsousa at gcc dot gnu.org> ---
Updated patch:

https://gcc.gnu.org/pipermail/fortran/2021-June/056163.html

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

* [Bug fortran/97046] Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
  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
                   ` (7 preceding siblings ...)
  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
  10 siblings, 0 replies; 12+ messages in thread
From: jrfsousa at gcc dot gnu.org @ 2021-06-14 23:24 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #9 from José Rui Faustino de Sousa <jrfsousa at gcc dot gnu.org> ---
Created attachment 51018
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=51018&action=edit
Updated patch.

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

* [Bug fortran/97046] Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
  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
                   ` (8 preceding siblings ...)
  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
  10 siblings, 0 replies; 12+ messages in thread
From: cvs-commit at gcc dot gnu.org @ 2021-07-26 12:33 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #10 from CVS Commits <cvs-commit at gcc dot gnu.org> ---
The master branch has been updated by Tobias Burnus <burnus@gcc.gnu.org>:

https://gcc.gnu.org/g:0cbf03689e3e7d9d6002b8e5d159ef3716d0404c

commit r12-2511-g0cbf03689e3e7d9d6002b8e5d159ef3716d0404c
Author: Tobias Burnus <tobias@codesourcery.com>
Date:   Mon Jul 26 14:20:46 2021 +0200

    PR fortran/93308/93963/94327/94331/97046 problems raised by descriptor
handling

    Fortran: Fix attributes and bounds in ISO_Fortran_binding.

    2021-07-26  José Rui Faustino de Sousa  <jrfsousa@gmail.com>
                Tobias Burnus  <tobias@codesourcery.com>

            PR fortran/93308
            PR fortran/93963
            PR fortran/94327
            PR fortran/94331
            PR fortran/97046

    gcc/fortran/ChangeLog:

            * trans-decl.c (convert_CFI_desc): Only copy out the descriptor
            if necessary.
            * trans-expr.c (gfc_conv_gfc_desc_to_cfi_desc): Updated attribute
            handling which reflect a previous intermediate version of the
            standard. Only copy out the descriptor if necessary.

    libgfortran/ChangeLog:

            * runtime/ISO_Fortran_binding.c (cfi_desc_to_gfc_desc): Add code
            to verify the descriptor. Correct bounds calculation.
            (gfc_desc_to_cfi_desc): Add code to verify the descriptor.

    gcc/testsuite/ChangeLog:

            * gfortran.dg/ISO_Fortran_binding_1.f90: Add pointer attribute,
            this test is still erroneous but now it compiles.
            * gfortran.dg/bind_c_array_params_2.f90: Update regex to match
            code changes.
            * gfortran.dg/PR93308.f90: New test.
            * gfortran.dg/PR93963.f90: New test.
            * gfortran.dg/PR94327.c: New test.
            * gfortran.dg/PR94327.f90: New test.
            * gfortran.dg/PR94331.c: New test.
            * gfortran.dg/PR94331.f90: New test.
            * gfortran.dg/PR97046.f90: New test.

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

* [Bug fortran/97046] Bad interaction between lbound/ubound, allocatable arrays and bind(C) subroutine with dimension(..) parameter
  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
                   ` (9 preceding siblings ...)
  2021-07-26 12:33 ` cvs-commit at gcc dot gnu.org
@ 2021-10-19 10:25 ` burnus at gcc dot gnu.org
  10 siblings, 0 replies; 12+ messages in thread
From: burnus at gcc dot gnu.org @ 2021-10-19 10:25 UTC (permalink / raw)
  To: gcc-bugs

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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         Resolution|---                         |FIXED
             Status|ASSIGNED                    |RESOLVED
                 CC|                            |burnus at gcc dot gnu.org

--- Comment #11 from Tobias Burnus <burnus at gcc dot gnu.org> ---
FIXED (in GCC 12).

Thanks Igor for the testcase!

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