Bug 51605 - internal compiler error gfc_trans_block_construct, at fortran/trans-stmt.c:984
Summary: internal compiler error gfc_trans_block_construct, at fortran/trans-stmt.c:984
Status: RESOLVED FIXED
Alias: None
Product: gcc
Classification: Unclassified
Component: fortran (show other bugs)
Version: unknown
: P3 normal
Target Milestone: 4.7.0
Assignee: Not yet assigned to anyone
URL:
Keywords: rejects-valid
Depends on: 51610
Blocks:
  Show dependency treegraph
 
Reported: 2011-12-17 22:44 UTC by Dan Nagle
Modified: 2016-11-16 14:26 UTC (History)
4 users (show)

See Also:
Host:
Target:
Build:
Known to work:
Known to fail:
Last reconfirmed:


Attachments
output copied from shell window and source file (54.61 KB, application/x-gzip)
2011-12-17 22:44 UTC, Dan Nagle
Details
Draft patch (for the rejects-valid part, not for the ICE) (843 bytes, text/plain)
2011-12-19 11:39 UTC, Tobias Burnus
Details

Note You need to log in before you can comment on or make changes to this bug.
Description Dan Nagle 2011-12-17 22:44:19 UTC
Created attachment 26126 [details]
output copied from shell window and source file
Comment 1 Dan Nagle 2011-12-17 22:45:42 UTC
Compiles with fort 12.1, nagfor has a different problem.
Comment 2 Dominique d'Humieres 2011-12-17 23:25:30 UTC
After revision 181975, the 4.7 trunk gives the following errors

pr51605.f90:12578.24:

         integer_ptr => symbol_ptr
                        1
Error: Pointer assignment target is neither TARGET nor POINTER at (1)
pr51605.f90:12584.24:

         logical_ptr => symbol_ptr
                        1
Error: Pointer assignment target is neither TARGET nor POINTER at (1)
pr51605.f90:8367.24:

         integer_ptr => symbol_ptr
                        1
Error: Pointer assignment target is neither TARGET nor POINTER at (1)
pr51605.f90:8373.24:

         logical_ptr => symbol_ptr
                        1
Error: Pointer assignment target is neither TARGET nor POINTER at (1)

see pr48887 for the change in behavior.
Comment 3 kargls 2011-12-18 07:07:22 UTC
laptop:kargl[499] gfc4x --version
GNU Fortran (GCC) 4.7.0 20111124 (experimental)

laptop:kargl[500] gfc4x -o z coco.f90
coco.f90: In function 'process_coco_statement':
coco.f90:89:0: internal compiler error: in gfc_trans_block_construct, at fortran/trans-stmt.c:1193


Reduced testcase.


program coco

use, intrinsic :: iso_fortran_env, only: input_unit, output_unit

implicit none

character( len= *), parameter :: string_fmt = '( a)'
character( len= *), parameter :: integer_fmt = '( a, i10)'
character( len= *), parameter :: directory_fmt = '( a, i0, a)'
character( len= *), parameter :: conversion_fmt = '(i10)'
character( len= *), parameter :: null_string = ''
character( len= *), parameter :: mark_set_file = 'following SET file'
character( len= *), parameter :: alpha_chars = 'abcdefghijklmnopqrstuvwxyz'
character( len= *), parameter :: digit_chars = '0123456789'
character( len= *), parameter :: underscore = '_'
character( len= *), parameter :: alphanum_chars =  alpha_chars // digit_chars // underscore
character( len= *), parameter :: dot = '.'
character( len= *), parameter :: equals = '='
integer, parameter :: format_len = max(3, 12)
integer, parameter :: io_specifier_len = 16
integer, parameter :: conversion_len = 10
integer, parameter :: symbol_name_len = 31
integer, parameter :: free_form_len = 131
integer, parameter :: fixed_form_len = 72
integer, parameter :: source_line_len = 12
integer, parameter :: file_name_len = 256
integer, parameter :: max_continuations = 39

type, abstract :: symbol_t
   logical referenced
   class(symbol_t), pointer :: next
end type symbol_t

type, extends(symbol_t) :: logical_t
   logical logical_value
   type(logical_t), pointer :: next_logical
end type logical_t

type, extends(symbol_t) :: integer_t
   integer integer_value
   type(integer_t), pointer :: next_integer
end type integer_t

class( symbol_t), pointer :: first_symbol
class( symbol_t), pointer :: last_symbol

type( integer_t), pointer :: first_integer
type( integer_t), pointer :: last_integer

type( logical_t), pointer :: first_logical
type( logical_t), pointer :: last_logical

class( symbol_t), pointer :: first_sf_symbol
class( symbol_t), pointer :: last_sf_symbol

type( integer_t), pointer :: first_cl_integer
type( integer_t), pointer :: last_cl_integer

type( logical_t), pointer :: first_cl_logical
type( logical_t), pointer :: last_cl_logical

contains

subroutine process_coco_statement(coco_stmt)

   character(len= *), intent(in) :: coco_stmt

   class(symbol_t), pointer :: symbol_ptr

   type(integer_t), pointer :: integer_ptr
   type(logical_t), pointer :: logical_ptr
   integer eq_idx
   integer expr_idx

   nullify( symbol_ptr)

   eq_idx =  scan( coco_stmt( 1: symbol_name_len + len( equals)), equals)

   got_equals: if( eq_idx > 0 )then

      call seek_symbol_name( coco_stmt( 1: eq_idx - 1), symbol_ptr)

   end if got_equals

   if (associated(symbol_ptr))then

      expr_idx = eq_idx + len(equals)

      integer_or_logical: select type(symbol_ptr)
      type is(integer_t) integer_or_logical
         integer_ptr => symbol_ptr
         call process_integer_assignment( coco_stmt( expr_idx: ), integer_ptr)
      type is(logical_t) integer_or_logical
         logical_ptr => symbol_ptr
         call process_logical_assignment( coco_stmt( expr_idx: ), logical_ptr)
      class default integer_or_logical
         call msg_quit("target of assignment must ")
      end select integer_or_logical
   end if

end subroutine process_coco_statement

subroutine integer_or_logical( expr_str, flag)
character(len= *), intent(in) :: expr_str
logical, intent(out) :: flag
flag = .true.
end subroutine integer_or_logical

recursive subroutine eval_int_expr( int_expr, value)
character(len= *), intent(in) :: int_expr
integer, intent(out) :: value
value = 42
end subroutine eval_int_expr

end program coco
Comment 4 Tobias Burnus 2011-12-18 10:01:13 UTC
With the current GCC 4.7 I get for the original example (comment 0, attachment 26126 [details]) but also for Steve's reduced test case in comment 3 the error:

         integer_ptr => symbol_ptr
                        1
Error: Pointer assignment target is neither TARGET nor POINTER at (1)
[Cf. comment 2, PR 48887]

I believe the error message is correct due to (F2008, 16.5.1.6 Construct association):

"If the selector has the POINTER attribute, it shall be associated; the
associate name is associated with the target of the pointer and does not have
the POINTER attribute."

And due to the error message, the code part which ICEs cannot be reached.


Dan: You wrote: "Compiles with fort 12.1, nagfor has a different problem."

Do you believe the code is valid, if so, why doesn't 16.5.1.6 apply? If it applies, can you construct a valid example which still fails?


Dan, Stave: If possible, please also update your GCC to 2011-12-11 or newer - at least if you use OOP/polymorphism features. (You might be able to get a newer binary from http://gcc.gnu.org/wiki/GFortranBinaries )
Comment 5 Dan Nagle 2011-12-18 13:13:48 UTC
Citations from 10-007r1.pdf

[185:17-18] says the polymorphic symbol_ptr takes the type of the type guard within the type guard.

[171:7-8] says the associating entity loses the pointer attribute but keeps the target attribute.
(It has the target attribute because it was a pointer outside the type guard.)

Therefore I believe it's conforming to point to the associating entity with a typed pointer.
(integer_ptr => symbol_ptr)

My analysis could be faulty.

I'm using the gfortran I'm using because it had a Mac installer.  I thought 4.6.2 was fairly recent.

This is all new stuff and I'm learning it myself and getting surprised here and there.

Thanks for your efforts.
Comment 6 Tobias Burnus 2011-12-18 14:11:00 UTC
(In reply to comment #5)
> Therefore I believe it's conforming to point to the associating entity with a
> typed pointer.
> (integer_ptr => symbol_ptr)

I should have read the test case more carefully. The associate name is on the right and not on the left hand side. I concur that in this case the associate name should get the target attribute. Thanks for pointing that out!


> I'm using the gfortran I'm using because it had a Mac installer.  I thought
> 4.6.2 was fairly recent.

Yes, 4.6.2 is the latest release; however, the 4.6 branch is now 9 months old and thus misses all the changes for 4.7, which will be released in March. [The trunk (= main development line) is currently in the stabilization and bug fixing Stage 3.]

As Fortran's polymorphism support is quite complicated, implementing it takes a while and the current implementations are still incomplete and buggy. (That's the case for all compilers, though the stability and completeness varies.)

In case of GCC/gfortran, 4.7 now supports constructors (DT name = generic function name) and - since 2011-12-11 -polymorphic arrays. Additionally, several other bugs were fixed. See http://gcc.gnu.org/wiki/OOP for an overview.

There is a fairly new 4.7 binary available for Darwin (cf. http://gcc.gnu.org/wiki/GFortranBinaries#MacOS ) but the build is almost 4 weeks old and thus does not yet support polymorphic arrays. My idea was that I will asked for a new build soon, but only after a few additional OOP bugs have been fixed.
Comment 7 Steve Kargl 2011-12-18 16:39:24 UTC
On Sun, Dec 18, 2011 at 10:01:13AM +0000, burnus at gcc dot gnu.org wrote:
> 
> Dan, Stave: If possible, please also update your GCC to 2011-12-11 or newer -
> at least if you use OOP/polymorphism features. (You might be able to get a
> newer binary from http://gcc.gnu.org/wiki/GFortranBinaries )
> 

I did the update last night whlie dreamed of sugarplums.
This morning with the new gfortran, I get the error messages
that you and Domonique report:

laptop:kargl[221] gfc4x -c coco.f90
coco.f90:91.24:

         integer_ptr => symbol_ptr
                        1
Error: Pointer assignment target is neither TARGET nor POINTER at (1)
coco.f90:94.24:

         logical_ptr => symbol_ptr
                        1
Error: Pointer assignment target is neither TARGET nor POINTER at (1)
Comment 8 Tobias Burnus 2011-12-19 11:39:55 UTC
Created attachment 26139 [details]
Draft patch (for the rejects-valid part, not for the ICE)

Draft patch, which allows again
  ptr => associate-name
It also fixes an ICE ("class_ok" part, "(a)") and issues with coarrays and select type. [Coarrays now fail after resolution with an ICE.]

Test cases (a) to (d):

type t
end type t
class(t), target :: p1               ! (a) Invalid (was ICEing before)
!class(t), allocatable, target :: p1 ! (b) Valid (unchanged by the patch)
!class(t), allocatable :: p1         ! (c) Correctly fails (ditto)
!class(t), pointer :: p1             ! (d) Valid (now accepted)
class(t), pointer :: p2

select type(p1)
  type is(t)
    p2 => p1
  class is(t)
    p2 => p1
end select
end

 * * *

Having fixed the rejects-valid issue, one again hits:
  internal compiler error: in gfc_trans_block_construct, at fortran/trans-stmt.c:1215

1209      ns = code->ext.block.ns;
1211      sym = ns->proc_name;
1215      gcc_assert (!sym->tlink);

Here, "sym->name" is "eval_int_expr" and sym->tlink == sym.


The issue is seemingly the following code in an internal procedure:
      integer_or_logical: select type(symbol_ptr)
      ...
      end select integer_or_logical

and then another internal procedure:

  subroutine integer_or_logical( expr_str, flag)
    ...
  end subroutine integer_or_logical

  recursive subroutine eval_int_expr( int_expr, value)

The label "integer_or_logical" of the block some clashes with the same-named subroutine - and thus marks the subroutine which follows somehow as EXPR_BLOCK?!?
Comment 9 Tobias Burnus 2011-12-19 13:17:15 UTC
Dan: Your program should work (with 4.6.2 - or with 4.7 + my patch) if you either change either the SELECT TYPE label or the subroutine name from "integer_or_logical" to something else.

 * * *

Reduced test case for the ICE:

contains
  subroutine foo
    BLOCK_NAME: block
    end block BLOCK_NAME
  end subroutine foo

  subroutine BLOCK_NAME()
  end subroutine BLOCK_NAME

  subroutine bar()
  end subroutine bar
end
Comment 10 Tobias Burnus 2011-12-19 15:30:29 UTC
Author: burnus
Date: Mon Dec 19 15:30:23 2011
New Revision: 182484

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=182484
Log:
2011-12-19  Tobias Burnus  <burnus@net-b.de>

        PR fortran/51605
        * match.c (gfc_match_select_type): Handle
        scalar polymophic coarrays.
        (select_type_set_tmp, ): Ditto; avoid segfault if !class_ok.
        * primary.c (gfc_match_rvalue): Avoid segfault if !class_ok.
        * resolve.c (resolve_select_type): Ditto.
        (resolve_assoc_var): Fix setting the TARGET attribute for
        polymorphic selectors which are pointers.

2011-12-19  Tobias Burnus  <burnus@net-b.de>

        PR fortran/51605
        * gfortran.dg/select_type_25.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/select_type_25.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/match.c
    trunk/gcc/fortran/primary.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/testsuite/ChangeLog
Comment 11 Dan Nagle 2011-12-19 15:51:40 UTC
Hi,

I can confirm that changing the label of the select type to

integer_or_logical_or_error

removes the ICE.

I did so at lines 9325 and 13536 in the original source.

The new label is a better description of the purpose of the select type anyway.

Thanks, everyone!  The new version of coco has some (I think anyway)
good new features, and some older stuff removed, as per requests.
So it's very good to have gfortran on the list of compilers known to work.

The new coco is in testing now, but I hope to be able to distribute it RSN.

On Dec 19, 2011, at 08:17 , burnus at gcc dot gnu.org wrote:

> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=51605
> 
> --- Comment #9 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-12-19 13:17:15 UTC ---
> Dan: Your program should work (with 4.6.2 - or with 4.7 + my patch) if you
> either change either the SELECT TYPE label or the subroutine name from
> "integer_or_logical" to something else.
> 
> * * *
> 
> Reduced test case for the ICE:
> 
> contains
>  subroutine foo
>    BLOCK_NAME: block
>    end block BLOCK_NAME
>  end subroutine foo
> 
>  subroutine BLOCK_NAME()
>  end subroutine BLOCK_NAME
> 
>  subroutine bar()
>  end subroutine bar
> end
> 
> -- 
> Configure bugmail: http://gcc.gnu.org/bugzilla/userprefs.cgi?tab=email
> ------- You are receiving this mail because: -------
> You reported the bug.
Comment 12 Tobias Burnus 2011-12-19 18:41:24 UTC
(In reply to comment #9)
>   subroutine foo
>     BLOCK_NAME: block
>     end block BLOCK_NAME
>   end subroutine foo
>   subroutine BLOCK_NAME()
>   end subroutine BLOCK_NAME

The problem is the call to "gfc_fixup_sibling_symbols" which finds in "subroutine foo" the symbol "block_name" (FL_LABEL) - and overrides it with the subroutine (FL_PROCEDURE).

The source code has:
>             /* By 14.6.1.3, host association should be excluded
>                for the following.  */

I think it missed F95's
"(13) The name of a named construct"

Patch:
--- a/gcc/fortran/parse.c
+++ b/gcc/fortran/parse.c
@@ -3908,6 +3908,7 @@ gfc_fixup_sibling_symbols (gfc_symbol *sym, gfc_namespace *siblings)
                  || old_sym->attr.intrinsic
                  || old_sym->attr.generic
                  || old_sym->attr.flavor == FL_NAMELIST
+                 || old_sym->attr.flavor == FL_LABEL
                  || old_sym->attr.proc == PROC_ST_FUNCTION))
        {
          /* Replace it with the symbol from the parent namespace.  */
Comment 13 Tobias Burnus 2011-12-19 20:18:30 UTC
Author: burnus
Date: Mon Dec 19 20:18:18 2011
New Revision: 182497

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=182497
Log:
2011-12-19  Tobias Burnus  <burnus@net-b.de>

        PR fortran/51605
        * parse.c (gfc_fixup_sibling_symbols): Regard FL_LABEL as
        local symbol.

2011-12-19  Tobias Burnus  <burnus@net-b.de>

        PR fortran/51605
        * gfortran.dg/block_10.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/block_10.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/parse.c
    trunk/gcc/testsuite/ChangeLog
Comment 14 Tobias Burnus 2011-12-19 20:25:03 UTC
FIXED on the trunk (4.7).

Thanks Dan for both the bug report regarding the internal compiler error and named constructors [fixed for 4.7 with commit of comment 13] - and for pointing out the "target" attribute issue in comment 5 [only affected 4.7; fixed with commit of comment 10].