public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables
@ 2023-03-20  9:20 juergen.reuter at desy dot de
  2023-03-20  9:29 ` [Bug fortran/109209] [13 " rguenth at gcc dot gnu.org
                   ` (18 more replies)
  0 siblings, 19 replies; 20+ messages in thread
From: juergen.reuter at desy dot de @ 2023-03-20  9:20 UTC (permalink / raw)
  To: gcc-bugs

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

            Bug ID: 109209
           Summary: [13.0 regression] erroneous error on assignment of
                    alloctables
           Product: gcc
           Version: 13.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: juergen.reuter at desy dot de
  Target Milestone: ---

Some commit between last week and now, so between March 12 and March 19, has
created a regression, so gfortran throws a (presumably wrong) error message:
resonances_sub.f90:816:4:
  816 |     history_new(1:s) = res_set%history(1:s)
      |    1
Error: Component to the right of a part reference with nonzero rank must not
have the ALLOCATABLE attribute at (1)
resonances_sub.f90:816:23:
  816 |     history_new(1:s) = res_set%history(1:s)
      |                       1
Error: Component to the right of a part reference with nonzero rank must not
have the ALLOCATABLE attribute at (1)

This is a first part of the code below, I will hopefully provide a full
reproducer later one.


   810    module subroutine resonance_history_set_expand (res_set)
   811      class(resonance_history_set_t), intent(inout) :: res_set
   812      type(resonance_history_t), dimension(:), allocatable :: history_new
   813      integer :: s
   814      s = size (res_set%history)
   815      allocate (history_new (2 * s))
   816      history_new(1:s) = res_set%history(1:s)
   817      call move_alloc (history_new, res_set%history)
   818    end subroutine resonance_history_set_expand

   58    type :: resonance_info_t
    59       type(flavor_t) :: flavor
    60       type(resonance_contributors_t) :: contributors
    61    contains
    62       procedure :: copy => resonance_info_copy
    63       procedure :: write => resonance_info_write
    64       procedure, private :: resonance_info_init_pdg
    65       procedure, private :: resonance_info_init_flv
    66       generic :: init => resonance_info_init_pdg,
resonance_info_init_flv
    67       procedure, private :: resonance_info_equal
    68       generic :: operator(==) => resonance_info_equal
    69       procedure :: mapping => resonance_info_mapping
    70       procedure, private :: get_n_contributors =>
resonance_info_get_n_contributors
    71       procedure, private :: contains => resonance_info_contains
    72       procedure :: evaluate_distance => resonance_info_evaluate_distance
    73       procedure :: evaluate_gaussian => resonance_info_evaluate_gaussian
    74       procedure :: is_on_shell => resonance_info_is_on_shell
    75       procedure :: as_omega_string => resonance_info_as_omega_string
    76    end type resonance_info_t
    77  
    78    type :: resonance_history_t
    79       type(resonance_info_t), dimension(:), allocatable :: resonances
    80       integer :: n_resonances = 0
    81    contains
    82       procedure :: clear => resonance_history_clear
    83       procedure :: copy => resonance_history_copy
    84       procedure :: write => resonance_history_write
    85       procedure, private :: resonance_history_assign
    86       generic :: assignment(=) => resonance_history_assign
    87       procedure, private :: resonance_history_equal
    88       generic :: operator(==) => resonance_history_equal
    89       procedure, private :: resonance_history_contains
    90       generic :: operator(.contains.) => resonance_history_contains
    91       procedure :: add_resonance => resonance_history_add_resonance
    92       procedure :: remove_resonance =>
resonance_history_remove_resonance
    93       procedure :: add_offset => resonance_history_add_offset
    94       procedure :: contains_leg => resonance_history_contains_leg
    95       procedure :: mapping => resonance_history_mapping
    96       procedure :: only_has_n_contributors => &
    97            resonance_history_only_has_n_contributors
    98       procedure :: has_flavor => resonance_history_has_flavor
    99       procedure :: evaluate_distances =>
resonance_history_evaluate_distances
   100       procedure :: evaluate_gaussian =>
resonance_history_evaluate_gaussian
   101       procedure :: is_on_shell => resonance_history_is_on_shell
   102       procedure :: as_omega_string => resonance_history_as_omega_string
   103       procedure :: to_tree => resonance_history_to_tree
   104    end type resonance_history_t

  129    type :: resonance_history_set_t
   130       private
   131       logical :: complete = .false.
   132       integer :: n_filter = 0
   133       type(resonance_history_t), dimension(:), allocatable :: history
   134       type(index_array_t), dimension(:), allocatable :: contains_this
   135       type(resonance_tree_t), dimension(:), allocatable :: tree
   136       integer :: last = 0
   137     contains
   138       procedure :: write => resonance_history_set_write
   139       procedure :: init => resonance_history_set_init
   140       procedure :: enter => resonance_history_set_enter
   141       procedure :: freeze => resonance_history_set_freeze
   142       procedure :: determine_on_shell_histories &
   143            => resonance_history_set_determine_on_shell_histories
   144       procedure :: evaluate_gaussian =>
resonance_history_set_evaluate_gaussian
   145       procedure :: get_n_history => resonance_history_set_get_n_history
   146       procedure :: get_history => resonance_history_set_get_history
   147       procedure :: to_array => resonance_history_set_to_array
   148       procedure :: get_tree => resonance_history_set_get_tree
   149       procedure, private :: expand => resonance_history_set_expand
   150    end type resonance_history_set_t

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
@ 2023-03-20  9:29 ` rguenth at gcc dot gnu.org
  2023-03-20 11:37 ` juergen.reuter at desy dot de
                   ` (17 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: rguenth at gcc dot gnu.org @ 2023-03-20  9:29 UTC (permalink / raw)
  To: gcc-bugs

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

Richard Biener <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Priority|P3                          |P4
            Summary|[13.0 regression] erroneous |[13 regression] erroneous
                   |error on assignment of      |error on assignment of
                   |alloctables                 |alloctables
   Target Milestone|---                         |13.0

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
  2023-03-20  9:29 ` [Bug fortran/109209] [13 " rguenth at gcc dot gnu.org
@ 2023-03-20 11:37 ` juergen.reuter at desy dot de
  2023-03-20 14:35 ` juergen.reuter at desy dot de
                   ` (16 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: juergen.reuter at desy dot de @ 2023-03-20 11:37 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #1 from Jürgen Reuter <juergen.reuter at desy dot de> ---
Created attachment 54710
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=54710&action=edit
First still pretty large reproducer

I will provide a smaller reproducer soon.

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
  2023-03-20  9:29 ` [Bug fortran/109209] [13 " rguenth at gcc dot gnu.org
  2023-03-20 11:37 ` juergen.reuter at desy dot de
@ 2023-03-20 14:35 ` juergen.reuter at desy dot de
  2023-03-20 15:51 ` juergen.reuter at desy dot de
                   ` (15 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: juergen.reuter at desy dot de @ 2023-03-20 14:35 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #2 from Jürgen Reuter <juergen.reuter at desy dot de> ---
Created attachment 54712
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=54712&action=edit
Second, single-file reproducer, still 6295 lines

Still further reducing, stay tuned.

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (2 preceding siblings ...)
  2023-03-20 14:35 ` juergen.reuter at desy dot de
@ 2023-03-20 15:51 ` juergen.reuter at desy dot de
  2023-03-20 15:54 ` juergen.reuter at desy dot de
                   ` (14 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: juergen.reuter at desy dot de @ 2023-03-20 15:51 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from Jürgen Reuter <juergen.reuter at desy dot de> ---
Created attachment 54713
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=54713&action=edit
Promised short reproducer, 73 lines

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (3 preceding siblings ...)
  2023-03-20 15:51 ` juergen.reuter at desy dot de
@ 2023-03-20 15:54 ` juergen.reuter at desy dot de
  2023-03-20 16:00 ` juergen.reuter at desy dot de
                   ` (13 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: juergen.reuter at desy dot de @ 2023-03-20 15:54 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #4 from Jürgen Reuter <juergen.reuter at desy dot de> ---
Here is the promised reproducer, which fails even when not using submodules:
$ gfortran -c reproducer.f90 
reproducer.f90:69:4:

   69 |     history_new(1:s) = res_set%history(1:s)
      |    1
Error: Component to the right of a part reference with nonzero rank must not
have the ALLOCATABLE attribute at (1)
reproducer.f90:69:23:

   69 |     history_new(1:s) = res_set%history(1:s)
      |                       1
Error: Component to the right of a part reference with nonzero rank must not
have the ALLOCATABLE attribute at (1)



module resonances
  implicit none
  private

  type :: t1_t
     integer, dimension(:), allocatable :: c
   contains
     procedure, private :: t1_assign
     generic :: assignment(=) => t1_assign
  end type t1_t

  type :: t3_t
     type(t1_t), dimension(:), allocatable :: resonances
     integer :: n_resonances = 0
  contains
     procedure, private :: t3_assign
     generic :: assignment(=) => t3_assign
  end type t3_t

  type :: resonance_branch_t
     integer :: i = 0
     integer, dimension(:), allocatable :: r_child
     integer, dimension(:), allocatable :: o_child
  end type resonance_branch_t

  type :: resonance_tree_t
     private
     integer :: n = 0
     type(resonance_branch_t), dimension(:), allocatable :: branch
  end type resonance_tree_t

  type :: t3_set_t
     private
     type(t3_t), dimension(:), allocatable :: history
     type(resonance_tree_t), dimension(:), allocatable :: tree
     integer :: last = 0
   contains
     procedure, private :: expand => t3_set_expand
  end type t3_set_t

contains

  pure subroutine t1_assign &
       (t1_out, t1_in)
    class(t1_t), intent(inout) :: t1_out
    class(t1_t), intent(in) :: t1_in
    if (allocated (t1_out%c))  deallocate (t1_out%c)
    if (allocated (t1_in%c)) then
       allocate (t1_out%c (size (t1_in%c)))
       t1_out%c = t1_in%c
    end if
  end subroutine t1_assign

  subroutine t3_assign (res_hist_out, res_hist_in)
    class(t3_t), intent(out) :: res_hist_out
    class(t3_t), intent(in) :: res_hist_in
    if (allocated (res_hist_in%resonances)) then
       res_hist_out%resonances = res_hist_in%resonances
       res_hist_out%n_resonances = res_hist_in%n_resonances
    end if
  end subroutine t3_assign

  module subroutine t3_set_expand (res_set)
    class(t3_set_t), intent(inout) :: res_set
    type(t3_t), dimension(:), allocatable :: history_new
    integer :: s
    s = size (res_set%history)
    allocate (history_new (2 * s))
    history_new(1:s) = res_set%history(1:s)
    call move_alloc (history_new, res_set%history)
  end subroutine t3_set_expand

end module resonances

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (4 preceding siblings ...)
  2023-03-20 15:54 ` juergen.reuter at desy dot de
@ 2023-03-20 16:00 ` juergen.reuter at desy dot de
  2023-03-20 16:05 ` juergen.reuter at desy dot de
                   ` (12 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: juergen.reuter at desy dot de @ 2023-03-20 16:00 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from Jürgen Reuter <juergen.reuter at desy dot de> ---
This could be either this commit
commit d7caf313525a46f200d7f5db1ba893f853774aee
Author: Paul Thomas <pault@gcc.gnu.org>
Date:   Sat Mar 18 07:56:23 2023 +0000
/Fortran

I think, it is NOT this one: 
commit 5889c7bd46a45dc07ffb77ec0d698e18e0b99840
Author: Paul Thomas <pault@gcc.gnu.org>
Date:   Mon Mar 20 06:13:54 2023 +0000
    Fortran: Allow external function from in an associate block [PR87127]

NOR this one:
commit 5426ab34643d9e6502f3ee572891a03471fa33ed
Author: Harald Anlauf <anlauf@gmx.de>
Date:   Fri Mar 17 22:24:49 2023 +0100
    Fortran: procedures with BIND(C) attribute require explicit interface
[PR85877]

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (5 preceding siblings ...)
  2023-03-20 16:00 ` juergen.reuter at desy dot de
@ 2023-03-20 16:05 ` juergen.reuter at desy dot de
  2023-03-20 16:25 ` juergen.reuter at desy dot de
                   ` (11 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: juergen.reuter at desy dot de @ 2023-03-20 16:05 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #6 from Jürgen Reuter <juergen.reuter at desy dot de> ---
Actually could be also this commit here:
commit 901edd99b44976b3c2b13a7d525d9e315540186a
Author: Harald Anlauf <anlauf@gmx.de>
Date:   Tue Mar 14 20:23:06 2023 +0100

    Fortran: rank checking with explicit-/assumed-size arrays and CLASS
[PR58331]

    gcc/fortran/ChangeLog:

            PR fortran/58331
            * interface.cc (compare_parameter): Adjust check of array dummy
            arguments to handle the case of CLASS variables.

    gcc/testsuite/ChangeLog:

            PR fortran/58331
            * gfortran.dg/class_dummy_10.f90: New test.

    Co-authored-by: Tobias Burnus <tobias@codesourcery.com>

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (6 preceding siblings ...)
  2023-03-20 16:05 ` juergen.reuter at desy dot de
@ 2023-03-20 16:25 ` juergen.reuter at desy dot de
  2023-03-20 16:48 ` burnus at gcc dot gnu.org
                   ` (10 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: juergen.reuter at desy dot de @ 2023-03-20 16:25 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #7 from Jürgen Reuter <juergen.reuter at desy dot de> ---
It looks like it is NOT Harald's and Tobias' commit,
https://github.com/gcc-mirror/gcc/commit/901edd99b44976b3c2b13a7d525d9e315540186a
I reverted that one, and still get the error.

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (7 preceding siblings ...)
  2023-03-20 16:25 ` juergen.reuter at desy dot de
@ 2023-03-20 16:48 ` burnus at gcc dot gnu.org
  2023-03-20 16:54 ` juergen.reuter at desy dot de
                   ` (9 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: burnus at gcc dot gnu.org @ 2023-03-20 16:48 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #8 from Tobias Burnus <burnus at gcc dot gnu.org> ---
The debugger shows for the example in comment 4 for the line

   69 |     history_new(1:s) = res_set%history(1:s)

the following expression:

(gdb) p gfc_debug_expr(expr)
t3_set_expand:history_new(1:__convert_i4_i8[[((t3_set_expand:s))]]) %
resonances(FULL)

That's F03:C614 - or in F2018:

C919 (R911) There shall not be more than one part-ref with nonzero rank. A
part-name to the right of a part-ref with nonzero rank shall not have the
ALLOCATABLE or POINTER attribute.

For the 'expr' shown in the debugger, that's violated as 'resonances' is
allocatable.


The 'expr' shown above is generated via
   generate_component_assignments -> gfc_resolve_expr
     -> resolve_variable -> gfc_resolve_ref
where generate_component_assignments's gfc_debug_code(*code) is
  ASSIGN
    t3_set_expand:history_new(1:__convert_i4_i8[[((t3_set_expand:s))]])
    t3_set_expand:res_set % history(1:__convert_i4_i8[[((t3_set_expand:s))]])
which matches the user code and looks fine.

(BTW: We should also check whether there is now an issue with generating
redundant (re)allocate on assignment code in trans*.cc.)

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (8 preceding siblings ...)
  2023-03-20 16:48 ` burnus at gcc dot gnu.org
@ 2023-03-20 16:54 ` juergen.reuter at desy dot de
  2023-03-20 16:56 ` juergen.reuter at desy dot de
                   ` (8 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: juergen.reuter at desy dot de @ 2023-03-20 16:54 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #9 from Jürgen Reuter <juergen.reuter at desy dot de> ---
(In reply to Jürgen Reuter from comment #4)
>
>   module subroutine t3_set_expand (res_set)
>     class(t3_set_t), intent(inout) :: res_set
>     type(t3_t), dimension(:), allocatable :: history_new
>     integer :: s
>     s = size (res_set%history)
>     allocate (history_new (2 * s))
>     history_new(1:s) = res_set%history(1:s)
>     call move_alloc (history_new, res_set%history)
>   end subroutine t3_set_expand
>   
> end module resonances

Actually, the 'module subroutine' here needs to be just 'subroutine'. gfortran
accepts this, nagfor doesn't.

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (9 preceding siblings ...)
  2023-03-20 16:54 ` juergen.reuter at desy dot de
@ 2023-03-20 16:56 ` juergen.reuter at desy dot de
  2023-03-20 17:19 ` pault at gcc dot gnu.org
                   ` (7 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: juergen.reuter at desy dot de @ 2023-03-20 16:56 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #10 from Jürgen Reuter <juergen.reuter at desy dot de> ---
(In reply to Tobias Burnus from comment #8)
> The debugger shows for the example in comment 4 for the line
> 
>    69 |     history_new(1:s) = res_set%history(1:s)
> 
> the following expression:
> 
> (gdb) p gfc_debug_expr(expr)
> t3_set_expand:history_new(1:__convert_i4_i8[[((t3_set_expand:s))]]) %
> resonances(FULL)
> 
> That's F03:C614 - or in F2018:
> 
> C919 (R911) There shall not be more than one part-ref with nonzero rank. A
> part-name to the right of a part-ref with nonzero rank shall not have the
> ALLOCATABLE or POINTER attribute.
> 
> For the 'expr' shown in the debugger, that's violated as 'resonances' is
> allocatable.
> 
> 
> The 'expr' shown above is generated via
>    generate_component_assignments -> gfc_resolve_expr
>      -> resolve_variable -> gfc_resolve_ref
> where generate_component_assignments's gfc_debug_code(*code) is
>   ASSIGN
>     t3_set_expand:history_new(1:__convert_i4_i8[[((t3_set_expand:s))]])
>     t3_set_expand:res_set % history(1:__convert_i4_i8[[((t3_set_expand:s))]])
> which matches the user code and looks fine.
> 
> (BTW: We should also check whether there is now an issue with generating
> redundant (re)allocate on assignment code in trans*.cc.)

Thanks for checking, Tobias. Are you saying that the code violates the
standard, or the code generation after parsing by gcc/gfortran has generated
code violating the standard?

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (10 preceding siblings ...)
  2023-03-20 16:56 ` juergen.reuter at desy dot de
@ 2023-03-20 17:19 ` pault at gcc dot gnu.org
  2023-03-20 17:21 ` burnus at gcc dot gnu.org
                   ` (6 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu.org @ 2023-03-20 17:19 UTC (permalink / raw)
  To: gcc-bugs

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

Paul Thomas <pault at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever confirmed|0                           |1
   Last reconfirmed|                            |2023-03-20

--- Comment #11 from Paul Thomas <pault at gcc dot gnu.org> ---

> Thanks for checking, Tobias. Are you saying that the code violates the
> standard, or the code generation after parsing by gcc/gfortran has generated
> code violating the standard?

Hi Jürgen,

Its' the latter - see the end of this reply.

Other brands don't like your reproducer:

[pault@pc30 pr37336]$ rm ./a.out;nagfor pr109209.f90 -g;./a.out
rm: cannot remove './a.out': No such file or directory
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7115
Error: pr109209.f90, line 63: Type-bound procedure T3_SET_EXPAND must be a
module procedure or external procedure with an explicit interface
       detected at T3_SET_EXPAND@(
Error: pr109209.f90, line 73: Undefined type-bound procedure T3_SET_EXPAND
[NAG Fortran Compiler pass 1 error termination, 2 errors]


[pault@pc30 pr37336]$ rm ./a.out;ifort pr109209.f90 -g;./a.out
rm: cannot remove './a.out': No such file or directory
pr109209.f90(63): error #6115: A separate interface body must have been
declared in the program unit or an ancestor of the program unit for the
separate module procedure.   [T3_SET_EXPAND]
  module subroutine t3_set_expand (res_set)
--------------------^
pr109209.f90(64): error #6451: A dummy argument name is required in this
context.   [RES_SET]
    class(t3_set_t), intent(inout) :: res_set
--------------------------------------^
pr109209.f90(38): error #8169: The specified interface is not declared.  
[T3_SET_EXPAND]
     procedure, private :: expand => t3_set_expand
-------------------------------------^
compilation aborted for pr109209.f90 (code 1)

both compile it just fine if you
s/module subroutine t3_set_expand/subroutine t3_set_expand/


Removing Harald's commit, commit 901edd99b44976b3c2b13a7d525d9e315540186a,
doesn't do the job.

However, removing my patch for pr37336 does indeed allow the code to compile as
before.

Everybody is happy with
  subroutine t3_set_expand (res_set)
    class(t3_set_t), intent(inout) :: res_set
    type(t3_t), dimension(:), allocatable :: history_new
    integer :: s, i
    s = size (res_set%history)
    allocate (history_new (2 * s))
    do i = 1,s
      history_new(i) = res_set%history(i)
    end do
    call move_alloc (history_new, res_set%history)
  end subroutine t3_set_expand

Actually, I think that I have indeed introduced a bug since t3_t has a defined
assignment.

Give me 30 minutes:-)

Paul

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (11 preceding siblings ...)
  2023-03-20 17:19 ` pault at gcc dot gnu.org
@ 2023-03-20 17:21 ` burnus at gcc dot gnu.org
  2023-03-20 17:44 ` pault at gcc dot gnu.org
                   ` (5 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: burnus at gcc dot gnu.org @ 2023-03-20 17:21 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #12 from Tobias Burnus <burnus at gcc dot gnu.org> ---
I bet that's due to the finalization
  commit r13-6747-gd7caf313525a46f200d7f5db1ba893f853774aee
but I have not verified.

(In reply to Jürgen Reuter from comment #10)
> Thanks for checking, Tobias. Are you saying that the code violates the
> standard, or the code generation after parsing by gcc/gfortran has generated
> code violating the standard?

I think the code is OK as the constraint is not violated by the user code but
only by the code generated by the compiler internally from the user code.

However, I have only very narrowly looked at the gcc/fortran/*.cc code and not
tried to understand the Fortran code and what makes sense.
[TODO ↑]


The following fixes it, but ...

[TODO ↓]
... I have not come to a conclusion whether the
generated tree code (-fdump-tree-original) is correct with regards to
(re)allocation on assignment or memory freeing.


diff --git a/gcc/fortran/gfortran.h b/gcc/fortran/gfortran.h
index 9bab2c40ead..8d4e276d8a3 100644
--- a/gcc/fortran/gfortran.h
+++ b/gcc/fortran/gfortran.h
@@ -2567,0 +2568,3 @@ typedef struct gfc_expr
+  /* Set if the component assignment was generated by the compiler.  */
+  unsigned int generated : 1;
+
diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc
index 1d973d12ff1..df3979ca8f4 100644
--- a/gcc/fortran/resolve.cc
+++ b/gcc/fortran/resolve.cc
@@ -5456 +5456,2 @@ gfc_resolve_ref (gfc_expr *expr)
-         if (current_part_dimension || seen_part_dimension)
+         if ((current_part_dimension || seen_part_dimension)
+             && !expr->generated)
@@ -5518 +5519,2 @@ gfc_resolve_ref (gfc_expr *expr)
-         && seen_part_dimension)
+         && seen_part_dimension
+         && !expr->generated)
@@ -11370,0 +11373,2 @@ build_assignment (gfc_exec_op op, gfc_expr *expr1,
gfc_expr *expr2,
+      this_code->expr1->generated = true;
+      this_code->expr2->generated = true;


* * * 

> >   module subroutine t3_set_expand (res_set)

> Actually, the 'module subroutine' here needs to be just 'subroutine'.
> gfortran accepts this, nagfor doesn't.

I filed PR 109218 for this issue.

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (12 preceding siblings ...)
  2023-03-20 17:21 ` burnus at gcc dot gnu.org
@ 2023-03-20 17:44 ` pault at gcc dot gnu.org
  2023-03-20 17:51 ` pault at gcc dot gnu.org
                   ` (4 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu.org @ 2023-03-20 17:44 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #13 from Paul Thomas <pault at gcc dot gnu.org> ---
(In reply to Tobias Burnus from comment #12)
> I bet that's due to the finalization
>   commit r13-6747-gd7caf313525a46f200d7f5db1ba893f853774aee
> but I have not verified.
> 
...snip...

See my reply above.

In trying to fix all the finalization issues, I found myself following 10.2.1.3
"Interpretation of intrinsic assignments" closely; in particular paragraph 13,
points (1) and (2) which define what to do with allocatable components.
Reverting the one line in my patch that effects this cures this problem and has
no effect on the finalization testcases.

I suggest that I do the reversion and that we worry about intrinsic assignment
of derived types another time, especially since the other brands compile the
code without complaint.

> 
> > Actually, the 'module subroutine' here needs to be just 'subroutine'.
> > gfortran accepts this, nagfor doesn't.
> 
> I filed PR 109218 for this issue.

Thanks, Tobias

Regards

Paul

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (13 preceding siblings ...)
  2023-03-20 17:44 ` pault at gcc dot gnu.org
@ 2023-03-20 17:51 ` pault at gcc dot gnu.org
  2023-03-20 17:55 ` anlauf at gcc dot gnu.org
                   ` (3 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu.org @ 2023-03-20 17:51 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #14 from Paul Thomas <pault at gcc dot gnu.org> ---
For the record, the fix is:

diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc
index 1d973d12ff1..1a03e458d99 100644
--- a/gcc/fortran/resolve.cc
+++ b/gcc/fortran/resolve.cc
@@ -11760,6 +11760,7 @@ generate_component_assignments (gfc_code **code,
gfc_namespace *ns)
         of all kinds and allocatable components.  */
       if (!gfc_bt_struct (comp1->ts.type)
          || comp1->attr.pointer
+         || comp1->attr.allocatable
          || comp1->attr.proc_pointer_comp
          || comp1->attr.class_pointer
          || comp1->attr.proc_pointer)

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (14 preceding siblings ...)
  2023-03-20 17:51 ` pault at gcc dot gnu.org
@ 2023-03-20 17:55 ` anlauf at gcc dot gnu.org
  2023-03-20 22:30 ` juergen.reuter at desy dot de
                   ` (2 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: anlauf at gcc dot gnu.org @ 2023-03-20 17:55 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #15 from anlauf at gcc dot gnu.org ---
JFTR: Nvidia also doesn't like the reproducer:

NVFORTRAN-S-1056-MODULE prefix is only allowed for subprograms that were
declared as separate module procedures (pr109209.f90: 63)
  0 inform,   0 warnings,   1 severes, 0 fatal for t3_set_expand

Removing the "module" prefix makes the code compile, same with Intel.
OTOH Crayftn 14.0 seems to be happy.

@Paul: I agree with your proposal.

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (15 preceding siblings ...)
  2023-03-20 17:55 ` anlauf at gcc dot gnu.org
@ 2023-03-20 22:30 ` juergen.reuter at desy dot de
  2023-03-21  6:22 ` cvs-commit at gcc dot gnu.org
  2023-03-21  7:14 ` pault at gcc dot gnu.org
  18 siblings, 0 replies; 20+ messages in thread
From: juergen.reuter at desy dot de @ 2023-03-20 22:30 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #16 from Jürgen Reuter <juergen.reuter at desy dot de> ---
(In reply to Paul Thomas from comment #14)
> For the record, the fix is:
> 
> diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc
> index 1d973d12ff1..1a03e458d99 100644
> --- a/gcc/fortran/resolve.cc
> +++ b/gcc/fortran/resolve.cc
> @@ -11760,6 +11760,7 @@ generate_component_assignments (gfc_code **code,
> gfc_namespace *ns)
>          of all kinds and allocatable components.  */
>        if (!gfc_bt_struct (comp1->ts.type)
>           || comp1->attr.pointer
> +         || comp1->attr.allocatable
>           || comp1->attr.proc_pointer_comp
>           || comp1->attr.class_pointer
>           || comp1->attr.proc_pointer)

I confirm that all of our code compiles again with this fix, and all our tests
pass. Thanks for the quick action, Paul, and also for the stamina to tackle the
finalization!

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (16 preceding siblings ...)
  2023-03-20 22:30 ` juergen.reuter at desy dot de
@ 2023-03-21  6:22 ` cvs-commit at gcc dot gnu.org
  2023-03-21  7:14 ` pault at gcc dot gnu.org
  18 siblings, 0 replies; 20+ messages in thread
From: cvs-commit at gcc dot gnu.org @ 2023-03-21  6:22 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #17 from CVS Commits <cvs-commit at gcc dot gnu.org> ---
The master branch has been updated by Paul Thomas <pault@gcc.gnu.org>:

https://gcc.gnu.org/g:3a9caf7883103bc3a80dfc9e4797bb849b3c211c

commit r13-6771-g3a9caf7883103bc3a80dfc9e4797bb849b3c211c
Author: Paul Thomas <pault@gcc.gnu.org>
Date:   Tue Mar 21 06:22:37 2023 +0000

    Fortran: Fix regression caused by PR37336 patch [PR109209]

    2023-03-21  Paul Thomas  <pault@gcc.gnu.org>

    gcc/fortran
            PR fortran/109209
            * resolve.cc (generate_component_assignments): Restore the
            exclusion of allocatable components from the loop.

    gcc/testsuite/
            PR fortran/109209
            * gfortran.dg/pr109209.f90: New test.

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

* [Bug fortran/109209] [13 regression] erroneous error on assignment of alloctables
  2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
                   ` (17 preceding siblings ...)
  2023-03-21  6:22 ` cvs-commit at gcc dot gnu.org
@ 2023-03-21  7:14 ` pault at gcc dot gnu.org
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu.org @ 2023-03-21  7:14 UTC (permalink / raw)
  To: gcc-bugs

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

Paul Thomas <pault at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |RESOLVED
         Resolution|---                         |FIXED

--- Comment #18 from Paul Thomas <pault at gcc dot gnu.org> ---
Fixed! Thanks for the report.

Paul

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

end of thread, other threads:[~2023-03-21  7:14 UTC | newest]

Thread overview: 20+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2023-03-20  9:20 [Bug fortran/109209] New: [13.0 regression] erroneous error on assignment of alloctables juergen.reuter at desy dot de
2023-03-20  9:29 ` [Bug fortran/109209] [13 " rguenth at gcc dot gnu.org
2023-03-20 11:37 ` juergen.reuter at desy dot de
2023-03-20 14:35 ` juergen.reuter at desy dot de
2023-03-20 15:51 ` juergen.reuter at desy dot de
2023-03-20 15:54 ` juergen.reuter at desy dot de
2023-03-20 16:00 ` juergen.reuter at desy dot de
2023-03-20 16:05 ` juergen.reuter at desy dot de
2023-03-20 16:25 ` juergen.reuter at desy dot de
2023-03-20 16:48 ` burnus at gcc dot gnu.org
2023-03-20 16:54 ` juergen.reuter at desy dot de
2023-03-20 16:56 ` juergen.reuter at desy dot de
2023-03-20 17:19 ` pault at gcc dot gnu.org
2023-03-20 17:21 ` burnus at gcc dot gnu.org
2023-03-20 17:44 ` pault at gcc dot gnu.org
2023-03-20 17:51 ` pault at gcc dot gnu.org
2023-03-20 17:55 ` anlauf at gcc dot gnu.org
2023-03-20 22:30 ` juergen.reuter at desy dot de
2023-03-21  6:22 ` cvs-commit at gcc dot gnu.org
2023-03-21  7:14 ` pault 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).