public inbox for fortran@gcc.gnu.org
 help / color / mirror / Atom feed
* [Patch, fortran] PR98897 - Erroneous procedure attribute for associate name
@ 2021-02-02 12:20 Paul Richard Thomas
  2021-02-02 13:59 ` Tobias Burnus
  0 siblings, 1 reply; 5+ messages in thread
From: Paul Richard Thomas @ 2021-02-02 12:20 UTC (permalink / raw)
  To: fortran, gcc-patches

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

This is more or less 'obvious' and does not require any further explanation.

Regtests with FC33/x86_64 - OK for master (and ....)?

Paul

Fortran: Fix calls to associate name typebound subroutines [PR98897].

2021-02-02  Paul Thomas  <pault@gcc.gnu.org>

gcc/fortran
PR fortran/98897
* match.c (gfc_match_call): Include associate names as possible
entities with typebound subroutines. The target needs to be
resolved for the type.

gcc/testsuite/
PR fortran/98897
* gfortran.dg/typebound_call_32.f90: New test.

[-- Attachment #2: submit.diff --]
[-- Type: text/x-patch, Size: 1070 bytes --]

diff --git a/gcc/fortran/match.c b/gcc/fortran/match.c
index f0469e25da6..2df6191d7e6 100644
--- a/gcc/fortran/match.c
+++ b/gcc/fortran/match.c
@@ -4999,10 +4999,16 @@ gfc_match_call (void)
   sym = st->n.sym;
 
   /* If this is a variable of derived-type, it probably starts a type-bound
-     procedure call.  */
-  if ((sym->attr.flavor != FL_PROCEDURE
-       || gfc_is_function_return_value (sym, gfc_current_ns))
-      && (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS))
+     procedure call. Associate variable targets have to be resolved for the
+     target type.  */
+  if (((sym->attr.flavor != FL_PROCEDURE
+	|| gfc_is_function_return_value (sym, gfc_current_ns))
+       && (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS))
+		||
+      (sym->assoc && sym->assoc->target
+       && gfc_resolve_expr (sym->assoc->target)
+       && (sym->assoc->target->ts.type == BT_DERIVED
+	   || sym->assoc->target->ts.type == BT_CLASS)))
     return match_typebound_call (st);
 
   /* If it does not seem to be callable (include functions so that the

[-- Attachment #3: typebound_call_32.f90 --]
[-- Type: text/x-fortran, Size: 839 bytes --]

! { dg-do run }
!
! Test the fix for PR98897 in which typebound subroutines of associate names
! were not recognised in a call. Functions were OK but this is tested below.
!
! Contributed by Damian Rouson  <damian@sourceryinstitute.org>
!
module output_data_m
  implicit none

  type output_data_t
    integer, private :: i = 0
  contains
    procedure output, return_value
  end type


contains
  subroutine output(self)
      implicit none
      class(output_data_t) self
      self%i = 1234
  end subroutine

  integer function return_value(self)
      implicit none
      class(output_data_t) self
      return_value = self%i
  end function
end module

  use output_data_m
  implicit none
  associate(output_data => output_data_t())
    call output_data%output
    if (output_data%return_value() .ne. 1234) stop 1
  end associate
end


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

* Re: [Patch, fortran] PR98897 - Erroneous procedure attribute for associate name
  2021-02-02 12:20 [Patch, fortran] PR98897 - Erroneous procedure attribute for associate name Paul Richard Thomas
@ 2021-02-02 13:59 ` Tobias Burnus
  2021-02-02 15:05   ` Paul Richard Thomas
  0 siblings, 1 reply; 5+ messages in thread
From: Tobias Burnus @ 2021-02-02 13:59 UTC (permalink / raw)
  To: Paul Richard Thomas, fortran, gcc-patches

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

Hi Paul,

On 02.02.21 13:20, Paul Richard Thomas via Gcc-patches wrote:
> This is more or less 'obvious' and does not require any further explanation.

Well, I am not sure whether calling resolve is premature or not. In any
case, it still fails for the attached testcase. (Related but separate
issue.)

The second testcase fails with "Selector at (1) has no type" / "Symbol
'var' at (1) has no IMPLICIT type".

Disclaimer: I am not 100% sure whether those two or your/the PR's
testcase is valid. (It fails to compile with ifort 19.1. I have not read
the spec and assume that the original testcase is valid.)

Thus, please confirm that all three are valid. If so, do you see a way
to make the two new ones pass as well? If we are sure that the current
patch is still the right approach, I am also fine to do it stepwise.

Thanks,

Tobias

> Regtests with FC33/x86_64 - OK for master (and ....)?
>
> Paul
>
> Fortran: Fix calls to associate name typebound subroutines [PR98897].
>
> 2021-02-02  Paul Thomas  <pault@gcc.gnu.org>
>
> gcc/fortran
> PR fortran/98897
> * match.c (gfc_match_call): Include associate names as possible
> entities with typebound subroutines. The target needs to be
> resolved for the type.
>
> gcc/testsuite/
> PR fortran/98897
> * gfortran.dg/typebound_call_32.f90: New test.
-----------------
Mentor Graphics (Deutschland) GmbH, Arnulfstrasse 201, 80634 München Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Frank Thürauf

[-- Attachment #2: foo.f90 --]
[-- Type: text/x-fortran, Size: 694 bytes --]

module m
  implicit none
contains
  subroutine double(i)
    integer :: i
    i = 2*i
  end subroutine double

  function bar() result(res)
    procedure(double), pointer :: res
    res => double
  end function bar
  subroutine foo(i)
    integer :: i

    ! This works:
    procedure(), pointer :: proc
    call double(i)
    proc => bar()
    call proc(i)

    ! This fails:
    associate (var => bar())
      call var(i)  ! { dg-bogus "VARIABLE attribute of 'var' conflicts with PROCEDURE attribute" }
    end associate
  end subroutine foo

end module m

program test
  use m
  implicit none (type, external)
  integer :: i
  i = 50
  call foo(i)
  if (i /= 50*2*2) stop 1
end program test

[-- Attachment #3: foo3.f90 --]
[-- Type: text/x-fortran, Size: 570 bytes --]

module m
  implicit none
contains
  subroutine double(i)
    integer :: i
    i = 2*i
  end subroutine double

  function bar() result(res)
    procedure(double), pointer :: res
    res => double
  end function bar

  subroutine foo(i)
    integer :: i
    procedure(bar) :: var

    procedure(double), pointer :: proc
    associate (var => bar())
      proc => var
    end associate
    call proc(i)
  end subroutine foo

end module m

program test
  use m
  implicit none (type, external)
  integer :: i
  i = 50
  call foo(i)
  if (i /= 50*2) stop 1
end program test

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

* Re: [Patch, fortran] PR98897 - Erroneous procedure attribute for associate name
  2021-02-02 13:59 ` Tobias Burnus
@ 2021-02-02 15:05   ` Paul Richard Thomas
  2021-02-02 15:56     ` Tobias Burnus
  0 siblings, 1 reply; 5+ messages in thread
From: Paul Richard Thomas @ 2021-02-02 15:05 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: fortran, gcc-patches, Damian Rouson

Hi Tobias,

ifort (IFORT) 2021.1 Beta 20201112 is happy with the testcase in the patch.

In foo.f90, if I remove
     call var(i)  ! { dg-bogus "VARIABLE attribute of 'var' conflicts with
PROCEDURE attribute" }
gfortran correctly complains
   23 |     associate (var => bar())
      |                      1
Error: Selector at (1) has no type
ifort complains:
../pr98897/foo.f90(11): error #8179: The procedure pointer and the
procedure target must both be functions or subroutines.
    res => double

The responses from both compilers to foo3.f90 are the same.

Cheers

Paul



On Tue, 2 Feb 2021 at 13:59, Tobias Burnus <tobias@codesourcery.com> wrote:

> Hi Paul,
>
> On 02.02.21 13:20, Paul Richard Thomas via Gcc-patches wrote:
> > This is more or less 'obvious' and does not require any further
> explanation.
>
> Well, I am not sure whether calling resolve is premature or not. In any
> case, it still fails for the attached testcase. (Related but separate
> issue.)
>
> The second testcase fails with "Selector at (1) has no type" / "Symbol
> 'var' at (1) has no IMPLICIT type".
>
> Disclaimer: I am not 100% sure whether those two or your/the PR's
> testcase is valid. (It fails to compile with ifort 19.1. I have not read
> the spec and assume that the original testcase is valid.)
>
> Thus, please confirm that all three are valid. If so, do you see a way
> to make the two new ones pass as well? If we are sure that the current
> patch is still the right approach, I am also fine to do it stepwise.
>
> Thanks,
>
> Tobias
>
> > Regtests with FC33/x86_64 - OK for master (and ....)?
> >
> > Paul
> >
> > Fortran: Fix calls to associate name typebound subroutines [PR98897].
> >
> > 2021-02-02  Paul Thomas  <pault@gcc.gnu.org>
> >
> > gcc/fortran
> > PR fortran/98897
> > * match.c (gfc_match_call): Include associate names as possible
> > entities with typebound subroutines. The target needs to be
> > resolved for the type.
> >
> > gcc/testsuite/
> > PR fortran/98897
> > * gfortran.dg/typebound_call_32.f90: New test.
> -----------------
> Mentor Graphics (Deutschland) GmbH, Arnulfstrasse 201, 80634 München
> Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Frank
> Thürauf
>


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

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

* Re: [Patch, fortran] PR98897 - Erroneous procedure attribute for associate name
  2021-02-02 15:05   ` Paul Richard Thomas
@ 2021-02-02 15:56     ` Tobias Burnus
  2021-02-12 13:36       ` Paul Richard Thomas
  0 siblings, 1 reply; 5+ messages in thread
From: Tobias Burnus @ 2021-02-02 15:56 UTC (permalink / raw)
  To: Paul Richard Thomas; +Cc: gcc-patches, fortran

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

Hi,

first, I have attached a new example – it works if I move bar/hello up,
but if 'foo' comes first, it fails. I think it is valid.
(ifort 19 also compiles it.)

Sorry for trying hard to find examples where it does not
work – but I have simply the feeling that resolving things
during parsing cannot work in all cases.

On the other hand, I think your patch at least does not break
valid code as I had feared before. :-)
Thus, in that sense it would work for me.

  * * *

Regarding my previous examples, they are invalid because of:

C1105  (R1105) expr shall not be a designator of a procedure pointer
        or a function reference that returns a procedure pointer.

However:

On 02.02.21 16:05, Paul Richard Thomas via Fortran wrote:

> In foo.f90, if I remove
>       call var(i)  ! { dg-bogus "VARIABLE attribute of 'var' conflicts with
> PROCEDURE attribute" }
> gfortran correctly complains
>     23 |     associate (var => bar())
>        |                      1
> Error: Selector at (1) has no type

Which is not quite right. bar() has a type – it returns
a procedure pointer; even in cases where gfortran could
know at parse time, it does not diagnose C1105 but shows
an odd error instead.

> ifort complains:
> ../pr98897/foo.f90(11): error #8179: The procedure pointer and the
> procedure target must both be functions or subroutines.
>      res => double
Okay, we found a bug in ifort. 'double' and 'res' have the same
interface by construction – and both are subroutines.
It seems to be a similar bug to the ifort bug I got before:
When 'double' is parsed, ifort expects that 'precision' follows
('double precision').

> The responses from both compilers to foo3.f90 are the same.

(I forgot to comment/remove 'procedure(bar) :: var' when
playing around.) Again, this code violates C1105 – and the
error messages are still odd.

> On Tue, 2 Feb 2021 at 13:59, Tobias Burnus <tobias@codesourcery.com> wrote:
> On 02.02.21 13:20, Paul Richard Thomas via Gcc-patches wrote:
>>> Regtests with FC33/x86_64 - OK for master (and ....)?
>>> Fortran: Fix calls to associate name typebound subroutines [PR98897].
>>>
>>> 2021-02-02  Paul Thomas  <pault@gcc.gnu.org>
>>>
>>> gcc/fortran
>>> PR fortran/98897
>>> * match.c (gfc_match_call): Include associate names as possible
>>> entities with typebound subroutines. The target needs to be
>>> resolved for the type.
>>>
>>> gcc/testsuite/
>>> PR fortran/98897
>>> * gfortran.dg/typebound_call_32.f90: New test.
-----------------
Mentor Graphics (Deutschland) GmbH, Arnulfstrasse 201, 80634 München Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Frank Thürauf

[-- Attachment #2: varfunc.f90 --]
[-- Type: text/x-fortran, Size: 350 bytes --]

module m
  implicit none
  type t
  contains
    procedure, nopass :: hello
  end type t
contains
  subroutine foo()
    associate (var => bar())
      call var%hello()
    end associate
  end subroutine foo
  subroutine hello
    print *, 'Hello'
  end
  type(t) function bar()
  end
end module m

program test
  use m
  call foo()
end program test

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

* Re: [Patch, fortran] PR98897 - Erroneous procedure attribute for associate name
  2021-02-02 15:56     ` Tobias Burnus
@ 2021-02-12 13:36       ` Paul Richard Thomas
  0 siblings, 0 replies; 5+ messages in thread
From: Paul Richard Thomas @ 2021-02-12 13:36 UTC (permalink / raw)
  To: Tobias Burnus, Damian Rouson; +Cc: gcc-patches, fortran

Hi All,

Following off-list discussion with Tobias, I have committed the patch as
submitted to 10- and 11-branches.

A rather general problem with parsing and matching, which arose from the
discussion, has been shunted into PR99065. If possible, I intend to fix
this by two pass parsing/matching of all contained procedures; first all
specification blocks and then, on the second pass, the code blocks. This
should eliminate the need for the likes of
parse.c(gfc_fixup_sibling_symbols) and some similar fixups in resolve.c.

Regards

Paul


On Tue, 2 Feb 2021 at 15:56, Tobias Burnus <tobias@codesourcery.com> wrote:

> Hi,
>
> first, I have attached a new example – it works if I move bar/hello up,
> but if 'foo' comes first, it fails. I think it is valid.
> (ifort 19 also compiles it.)
>
> Sorry for trying hard to find examples where it does not
> work – but I have simply the feeling that resolving things
> during parsing cannot work in all cases.
>
> On the other hand, I think your patch at least does not break
> valid code as I had feared before. :-)
> Thus, in that sense it would work for me.
>
>   * * *
>
> Regarding my previous examples, they are invalid because of:
>
> C1105  (R1105) expr shall not be a designator of a procedure pointer
>         or a function reference that returns a procedure pointer.
>
> However:
>
> On 02.02.21 16:05, Paul Richard Thomas via Fortran wrote:
>
> > In foo.f90, if I remove
> >       call var(i)  ! { dg-bogus "VARIABLE attribute of 'var' conflicts
> with
> > PROCEDURE attribute" }
> > gfortran correctly complains
> >     23 |     associate (var => bar())
> >        |                      1
> > Error: Selector at (1) has no type
>
> Which is not quite right. bar() has a type – it returns
> a procedure pointer; even in cases where gfortran could
> know at parse time, it does not diagnose C1105 but shows
> an odd error instead.
>
> > ifort complains:
> > ../pr98897/foo.f90(11): error #8179: The procedure pointer and the
> > procedure target must both be functions or subroutines.
> >      res => double
> Okay, we found a bug in ifort. 'double' and 'res' have the same
> interface by construction – and both are subroutines.
> It seems to be a similar bug to the ifort bug I got before:
> When 'double' is parsed, ifort expects that 'precision' follows
> ('double precision').
>
> > The responses from both compilers to foo3.f90 are the same.
>
> (I forgot to comment/remove 'procedure(bar) :: var' when
> playing around.) Again, this code violates C1105 – and the
> error messages are still odd.
>
> > On Tue, 2 Feb 2021 at 13:59, Tobias Burnus <tobias@codesourcery.com>
> wrote:
> > On 02.02.21 13:20, Paul Richard Thomas via Gcc-patches wrote:
> >>> Regtests with FC33/x86_64 - OK for master (and ....)?
> >>> Fortran: Fix calls to associate name typebound subroutines [PR98897].
> >>>
> >>> 2021-02-02  Paul Thomas  <pault@gcc.gnu.org>
> >>>
> >>> gcc/fortran
> >>> PR fortran/98897
> >>> * match.c (gfc_match_call): Include associate names as possible
> >>> entities with typebound subroutines. The target needs to be
> >>> resolved for the type.
> >>>
> >>> gcc/testsuite/
> >>> PR fortran/98897
> >>> * gfortran.dg/typebound_call_32.f90: New test.
> -----------------
> Mentor Graphics (Deutschland) GmbH, Arnulfstrasse 201, 80634 München
> Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Frank
> Thürauf
>


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

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

end of thread, other threads:[~2021-02-12 13:37 UTC | newest]

Thread overview: 5+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2021-02-02 12:20 [Patch, fortran] PR98897 - Erroneous procedure attribute for associate name Paul Richard Thomas
2021-02-02 13:59 ` Tobias Burnus
2021-02-02 15:05   ` Paul Richard Thomas
2021-02-02 15:56     ` Tobias Burnus
2021-02-12 13:36       ` Paul Richard Thomas

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