Dear Gilles, 

> -----Ursprüngliche Nachricht-----
> Von: Gilles Gouaillardet <gil...@rist.or.jp>
> Gesendet: Freitag, 12. April 2019 02:25
> An: Bader, Reinhold <reinhold.ba...@lrz.de>; Paul Richard Thomas
> <paul.richard.tho...@gmail.com>; fort...@gcc.gnu.org; gcc-patches <gcc-
> patc...@gcc.gnu.org>
> Betreff: Re: AW: [Patch, fortran] PRs 89843 and 90022 - C Fortran Interop
> fixes.
> 
> Reinhold,
> 
> 
> Thanks for the insights !
> 
> 
> That means there is currently an other issue since copy-in is performed even
> if the argument is declared as ASYNCHRONOUS.
> 
> 
> I gave the copy-in mechanism some more thoughts, and as a library
> developers, I can clearly see a need *not* to do that
> 
> on a case-by-case basis, mainly for performance reasons, but also to be
> friendly with legacy apps that are not strictly standard compliant.
> 
> At this stage, I think the best way to move forward is to add an other
> directive in the interface definition.
> 
> 
> for example, we could declare
> 
> 
> module foo
> 
> interface
> 
> subroutine bar_f08(buf) BIND(C, name="bar_c")
> 
> implicit none
> 
> !GCC$ ATTRIBUTES NO_COPY_IN :: buf

maybe so, but some care must be taken to perform proper checking in case 
copy-in is necessary - these situations exist as well. 
For example, if the declaration for buf is

TYPE(*), DIMENSION(..), INTENT(IN), CONTIGUOUS :: buf

and the actual argument is a discontiguous array section.

My preference is for the compiler to automatically avoid copy-in whenever 
possible.

Cheers
Reinhold


> 
> TYPE(*), DIMENSION(..), INTENT(IN) :: buf
> 
> end subroutine
> 
> end interface
> 
> end module
> 
> 
> Does this make sense ?
> 
> 
> Gilles
> 
> On 4/10/2019 4:22 PM, Bader, Reinhold wrote:
> > Hi Gilles,
> >
> >> I also found an other potential issue with copy-in.
> >>
> >> If in Fortran, we
> >>
> >> call foo(buf(0,0))
> >>
> >> then the C subroutine can only access buf(0,0), and other elements such
> >> as buf(1025,1025) cannot be accessed.
> >>
> >> Such elements are valid in buf, but out of bounds in the copy (that
> >> contains a single element).
> >>
> >> Strictly speaking, I cannot say whether this is a violation of the
> >> standard or not, but I can see how this will
> >>
> >> break a lot of existing apps (once again, those apps might be incorrect
> >> in the first place, but most of us got used to them working).
> >
> > The above call will only be conforming if the dummy argument is declared
> > assumed or explicit size.
> > Otherwise, the compiler should reject it due to rank mismatch. For
> assumed
> > rank, the call would be
> > legitimate, but the rank of the dummy argument is then zero. Even if no
> > copy-in is performed,
> > accessing data beyond the address range of that scalar is not strictly
> > allowed.
> >
> > Of more interest is the situation where the dummy argument in Fortran is
> > declared, e.g.,
> >
> > TYPE(*), ASYNCHRONOUS, INTENT(IN) :: BUF(..)
> >
> > The standard's semantics *forbids* performing copy-in/out in this case,
> IIRC.
> > Otherwise
> > ASYNCHRONOUS semantics would not work, and non-blocking MPI calls
> would fail
> > due
> > to buffers vanishing into thin air.
> >
> > Regards
> > Reinhold
> >
> >> To me, this is a second reason why copy-in is not desirable (at least as
> >> a default option).
> >>
> >>
> >>
> >> Cheers,
> >>
> >>
> >> Gilles
> >>
> >> On 4/9/2019 7:18 PM, Paul Richard Thomas wrote:
> >>> The most part of this patch is concerned with implementing calls from
> >>> C of of fortran bind c procedures with assumed shape or assumed rank
> >>> dummies to completely fix PR89843. The conversion of the descriptors
> >>> from CFI to gfc occur on entry to and reversed on exit from the
> >>> procedure.
> >>>
> >>> This patch is safe for trunk, even at this late stage, because its
> >>> effects are barricaded behind the tests for CFI descriptors. I believe
> >>> that it appropriately rewards the bug reporters to have this feature
> >>> work as well as possible at release.
> >>>
> >>> Between comments and the ChangeLogs, this patch is self explanatory.
> >>>
> >>> Bootstrapped and regtested on FC29/x86_64 - OK for trunk?
> >>>
> >>> Paul
> >>>
> >>> 2019-04-09  Paul Thomas  <pa...@gcc.gnu.org>
> >>>
> >>>       PR fortran/89843
> >>>       * trans-decl.c (gfc_get_symbol_decl): Assumed shape and assumed
> >>>       rank dummies of bind C procs require deferred initialization.
> >>>       (convert_CFI_desc): New procedure to convert incoming CFI
> >>>       descriptors to gfc types and back again.
> >>>       (gfc_trans_deferred_vars): Call it.
> >>>       * trans-expr.c (gfc_conv_gfc_desc_to_cfi_desc): Null the CFI
> >>>       descriptor pointer. Free the descriptor in all cases.
> >>>
> >>>       PR fortran/90022
> >>>       * trans-decl.c (gfc_get_symbol_decl): Make sure that the se
> >>>       expression is a pointer type before converting it to the symbol
> >>>       backend_decl type.
> >>>
> >>> 2019-04-09  Paul Thomas  <pa...@gcc.gnu.org>
> >>>
> >>>       PR fortran/89843
> >>>       * gfortran.dg/ISO_Fortran_binding_4.f90: Modify the value of x
> >>>       in ctg. Test the conversion of the descriptor types in the main
> >>>       program.
> >>>       * gfortran.dg/ISO_Fortran_binding_10.f90: New test.
> >>>       * gfortran.dg/ISO_Fortran_binding_10.c: Called by it.
> >>>
> >>>       PR fortran/90022
> >>>       * gfortran.dg/ISO_Fortran_binding_1.c: Correct the indexing for
> >>>       the computation of 'ans'. Also, change the expected results for
> >>>       CFI_is_contiguous to comply with standard.
> >>>       * gfortran.dg/ISO_Fortran_binding_1.f90: Correct the expected
> >>>       results for CFI_is_contiguous to comply with standard.
> >>>       * gfortran.dg/ISO_Fortran_binding_9.f90: New test.
> >>>       * gfortran.dg/ISO_Fortran_binding_9.c: Called by it.
> >>>
> >>> 2019-04-09  Paul Thomas  <pa...@gcc.gnu.org>
> >>>
> >>>       PR fortran/89843
> >>>       * runtime/ISO_Fortran_binding.c (cfi_desc_to_gfc_desc): Only
> >>>       return immediately if the source pointer is null. Bring
> >>>       forward the extraction of the gfc type. Extract the kind so
> >>>       that the element size can be correctly computed for sections
> >>>       and components of derived type arrays. Remove the free of the
> >>>       CFI descriptor since this is now done in trans-expr.c.
> >>>       (gfc_desc_to_cfi_desc): Only allocate the CFI descriptor if it
> >>>       is not null.
> >>>       (CFI_section): Normalise the difference between the upper and
> >>>       lower bounds by the stride to correctly calculate the extents
> >>>       of the section.
> >>>
> >>>       PR fortran/90022
> >>>       * runtime/ISO_Fortran_binding.c (CFI_is_contiguous) : Return
> >>>       1 for true and 0 otherwise to comply with the standard. Correct
> >>>       the contiguity check for rank 3 and greater by using the stride
> >>>       measure of the lower dimension rather than the element length.

Attachment: smime.p7s
Description: S/MIME cryptographic signature

Reply via email to