public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/38883]  New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts
@ 2009-01-16 20:47 dick dot hendrickson at gmail dot com
  2009-01-16 21:38 ` [Bug fortran/38883] [4.4 Regression] " burnus at gcc dot gnu dot org
                   ` (9 more replies)
  0 siblings, 10 replies; 11+ messages in thread
From: dick dot hendrickson at gmail dot com @ 2009-01-16 20:47 UTC (permalink / raw)
  To: gcc-bugs

The following program causes an internal compiler error.  If the single
reference to NF3 in the MVBITS argument list is changed to "3" the program
compiles and executes.

Dick Hendrickson

      module yg0009_stuff

! fails on Windows XP
! gcc version 4.4.0 20081219 (experimental) [trunk revision 142842] (GCC)

      type unseq
         integer I
      end type

      contains

      SUBROUTINE YG0009(TDA2L,NF4,NF3,NF1,MF1,MF4,MF3)
      TYPE(UNSEQ) TDA2L(4,3)

      CALL MVBITS (TDA2L(4:1:-1,1:3)%I,2,
     $   4, TDA2L(4:1:-1,1:NF3)%I, 3)

!  these also ICE, but seem needlessly complex
!      TYPE(UNSEQ) TDA2L(NF4,NF3)
!
!      CALL MVBITS (TDA2L(NF4:NF1:MF1,NF1:NF3)%I,2,
!     $   4, TDA2L(-MF4:-MF1:-NF1,-MF1:-MF3)%I, 3)
!  but, you might as well try them in your spare time ;)

      END SUBROUTINE

      end module yg0009_stuff

      program try_yg0009
      use yg0009_stuff
      type(unseq)  tda2l(4,3)

      call yg0009(tda2l,4,3,1,-1,-4,-3)

      end


C:\gfortran>gfortran try_yg0009.f
try_yg0009.f: In function 'yg0009':
try_yg0009.f:12: internal compiler error: in gfc_trans_allocate_array_storage,
a
t fortran/trans-array.c:558
Please submit a full bug report,
with preprocessed source if appropriate.
See <http://gcc.gnu.org/bugs.html> for instructions.


-- 
           Summary: Internal Compiler Error for MVBITS with derived type
                    argument that has run-time subscripts
           Product: gcc
           Version: 4.4.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: dick dot hendrickson at gmail dot com


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38883


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

* [Bug fortran/38883] [4.4 Regression] Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts
  2009-01-16 20:47 [Bug fortran/38883] New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts dick dot hendrickson at gmail dot com
@ 2009-01-16 21:38 ` burnus at gcc dot gnu dot org
  2009-01-16 21:43 ` jakub at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-01-16 21:38 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from burnus at gcc dot gnu dot org  2009-01-16 21:38 -------
Confirm.

Working: 4.4.0 20081029 (experimental) [trunk revision 141421]
Failing: 4.4.0 20081103 (experimental) [trunk revision 141544]
(assuming that my tree was clean back then)


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
           Keywords|                            |ice-on-valid-code
      Known to fail|                            |4.4.0
      Known to work|                            |4.3.2
   Last reconfirmed|0000-00-00 00:00:00         |2009-01-16 21:38:10
               date|                            |
            Summary|Internal Compiler Error for |[4.4 Regression] Internal
                   |MVBITS with derived type    |Compiler Error for MVBITS
                   |argument that has run-time  |with derived type argument
                   |subscripts                  |that has run-time subscripts
   Target Milestone|---                         |4.4.0


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38883


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

* [Bug fortran/38883] [4.4 Regression] Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts
  2009-01-16 20:47 [Bug fortran/38883] New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts dick dot hendrickson at gmail dot com
  2009-01-16 21:38 ` [Bug fortran/38883] [4.4 Regression] " burnus at gcc dot gnu dot org
@ 2009-01-16 21:43 ` jakub at gcc dot gnu dot org
  2009-01-16 21:47 ` mikael at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: jakub at gcc dot gnu dot org @ 2009-01-16 21:43 UTC (permalink / raw)
  To: gcc-bugs



-- 

jakub at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Priority|P3                          |P4


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38883


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

* [Bug fortran/38883] [4.4 Regression] Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts
  2009-01-16 20:47 [Bug fortran/38883] New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts dick dot hendrickson at gmail dot com
  2009-01-16 21:38 ` [Bug fortran/38883] [4.4 Regression] " burnus at gcc dot gnu dot org
  2009-01-16 21:43 ` jakub at gcc dot gnu dot org
@ 2009-01-16 21:47 ` mikael at gcc dot gnu dot org
  2009-01-18 14:28 ` [Bug fortran/38883] [4.4 Regression] ICE " burnus at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: mikael at gcc dot gnu dot org @ 2009-01-16 21:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from mikael at gcc dot gnu dot org  2009-01-16 21:47 -------
http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=141516  ?


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38883


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

* [Bug fortran/38883] [4.4 Regression] ICE for MVBITS with derived type argument that has run-time subscripts
  2009-01-16 20:47 [Bug fortran/38883] New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts dick dot hendrickson at gmail dot com
                   ` (2 preceding siblings ...)
  2009-01-16 21:47 ` mikael at gcc dot gnu dot org
@ 2009-01-18 14:28 ` burnus at gcc dot gnu dot org
  2009-01-18 19:16 ` burnus at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-01-18 14:28 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from burnus at gcc dot gnu dot org  2009-01-18 14:28 -------
Slightly reduced test case below. If the FROM= and TO= arguments ("A()%I") are
not the same, the program does not ICE. Neither does it if one changes the
bound "N2" to "2" (but it does if one changes the second argument to
"(2:1:-1)"). Thus the problem seems to be closely linked with needing to create
a copy of the second argument. That is related to PR 38887, where unpacking the
copied 2nd argument generated an ICE at run time.

      module yg0009_stuff
      implicit none
      type unseq
         integer I
      end type
      contains
      SUBROUTINE YG0009(A,N2)
      TYPE(UNSEQ) A(2)
      TYPE(UNSEQ) B(2)
      integer :: N2
      CALL MVBITS (A(1:2)%I,1, 1, A(1:N2)%I, 1)
      END SUBROUTINE
      end module yg0009_stuff


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
            Summary|[4.4 Regression] Internal   |[4.4 Regression] ICE for
                   |Compiler Error for MVBITS   |MVBITS with derived type
                   |with derived type argument  |argument that has run-time
                   |that has run-time subscripts|subscripts


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38883


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

* [Bug fortran/38883] [4.4 Regression] ICE for MVBITS with derived type argument that has run-time subscripts
  2009-01-16 20:47 [Bug fortran/38883] New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts dick dot hendrickson at gmail dot com
                   ` (3 preceding siblings ...)
  2009-01-18 14:28 ` [Bug fortran/38883] [4.4 Regression] ICE " burnus at gcc dot gnu dot org
@ 2009-01-18 19:16 ` burnus at gcc dot gnu dot org
  2009-01-20  9:47 ` domob at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-01-18 19:16 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from burnus at gcc dot gnu dot org  2009-01-18 19:16 -------
Some more data: Using

  printf("Node: tmp  = %s\n", tree_code_name[TREE_CODE (tmp)]);
  printf("Node: desc = %s\n",
         tree_code_name[TREE_CODE (gfc_get_element_type (TREE_TYPE (desc)))]);
  gcc_assert (tmp == gfc_get_element_type (TREE_TYPE (desc)));

one sees:

  Node: tmp  = record_type
  Node: desc = integer_type

desc gets its type via "gfc_get_array_type_bounds()" in
gfc_trans_create_temp_array. And then
  gfc_get_element_type (TREE_TYPE (desc))


And "tmp" via the following:
          if (fsym->attr.intent == INTENT_INOUT)
            initial = parmse.expr;
          else
            initial = NULL_TREE;
in gfc_conv_elemental_dependencies which then in
gfc_trans_allocate_array_storage gets accessed as:
              tmp = TREE_TYPE (initial); /* Pointer to descriptor.  */
              gcc_assert (TREE_CODE (tmp) == POINTER_TYPE);
              tmp = TREE_TYPE (tmp); /* The descriptor itself.  */
              tmp = gfc_get_element_type (tmp);


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38883


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

* [Bug fortran/38883] [4.4 Regression] ICE for MVBITS with derived type argument that has run-time subscripts
  2009-01-16 20:47 [Bug fortran/38883] New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts dick dot hendrickson at gmail dot com
                   ` (4 preceding siblings ...)
  2009-01-18 19:16 ` burnus at gcc dot gnu dot org
@ 2009-01-20  9:47 ` domob at gcc dot gnu dot org
  2009-01-25  8:36 ` domob at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: domob at gcc dot gnu dot org @ 2009-01-20  9:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from domob at gcc dot gnu dot org  2009-01-20 09:47 -------
(In reply to comment #2)
> http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=141516  ?
> 

Seems to be my fault, quite plausibly :D  I will work on this.


-- 

domob at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |domob at gcc dot gnu dot org
                   |dot org                     |
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2009-01-16 21:38:10         |2009-01-20 09:47:12
               date|                            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38883


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

* [Bug fortran/38883] [4.4 Regression] ICE for MVBITS with derived type argument that has run-time subscripts
  2009-01-16 20:47 [Bug fortran/38883] New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts dick dot hendrickson at gmail dot com
                   ` (5 preceding siblings ...)
  2009-01-20  9:47 ` domob at gcc dot gnu dot org
@ 2009-01-25  8:36 ` domob at gcc dot gnu dot org
  2009-01-27 18:08 ` domob at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: domob at gcc dot gnu dot org @ 2009-01-25  8:36 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from domob at gcc dot gnu dot org  2009-01-25 08:36 -------
(In reply to comment #4)
> in gfc_conv_elemental_dependencies which then in
> gfc_trans_allocate_array_storage gets accessed as:
>               tmp = TREE_TYPE (initial); /* Pointer to descriptor.  */
>               gcc_assert (TREE_CODE (tmp) == POINTER_TYPE);
>               tmp = TREE_TYPE (tmp); /* The descriptor itself.  */
>               tmp = gfc_get_element_type (tmp);

This is very likely the problem here; I guess 'tmp' should get integer_type
instead of record_type, too, and the code above misses to do so.

When I wrote this fragment, it was more or less just a trial-and-error process
as I (still) don't know the backend-stuff quite well; I will try to get the
correct sequence which will hopefully fix this problem.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38883


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

* [Bug fortran/38883] [4.4 Regression] ICE for MVBITS with derived type argument that has run-time subscripts
  2009-01-16 20:47 [Bug fortran/38883] New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts dick dot hendrickson at gmail dot com
                   ` (6 preceding siblings ...)
  2009-01-25  8:36 ` domob at gcc dot gnu dot org
@ 2009-01-27 18:08 ` domob at gcc dot gnu dot org
  2009-01-27 18:10 ` domob at gcc dot gnu dot org
  2009-01-29 17:44 ` hjl at gcc dot gnu dot org
  9 siblings, 0 replies; 11+ messages in thread
From: domob at gcc dot gnu dot org @ 2009-01-27 18:08 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from domob at gcc dot gnu dot org  2009-01-27 18:08 -------
Subject: Bug 38883

Author: domob
Date: Tue Jan 27 18:07:54 2009
New Revision: 143707

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=143707
Log:
2009-01-27  Daniel Kraft  <d@domob.eu>

        PR fortran/38883
        * trans-stmt.c (gfc_conv_elemental_dependencies):  Create temporary
        for the real type needed to make it work for subcomponent-references.

2009-01-27  Daniel Kraft  <d@domob.eu>

        PR fortran/38883
        * gfortran.dg/mvbits_6.f90:  New test.
        * gfortran.dg/mvbits_7.f90:  New test.
        * gfortran.dg/mvbits_8.f90:  New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/mvbits_6.f90
    trunk/gcc/testsuite/gfortran.dg/mvbits_7.f90
    trunk/gcc/testsuite/gfortran.dg/mvbits_8.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-stmt.c
    trunk/gcc/testsuite/ChangeLog


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38883


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

* [Bug fortran/38883] [4.4 Regression] ICE for MVBITS with derived type argument that has run-time subscripts
  2009-01-16 20:47 [Bug fortran/38883] New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts dick dot hendrickson at gmail dot com
                   ` (7 preceding siblings ...)
  2009-01-27 18:08 ` domob at gcc dot gnu dot org
@ 2009-01-27 18:10 ` domob at gcc dot gnu dot org
  2009-01-29 17:44 ` hjl at gcc dot gnu dot org
  9 siblings, 0 replies; 11+ messages in thread
From: domob at gcc dot gnu dot org @ 2009-01-27 18:10 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from domob at gcc dot gnu dot org  2009-01-27 18:10 -------
Fixed on trunk.


-- 

domob at gcc dot gnu dot org changed:

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


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38883


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

* [Bug fortran/38883] [4.4 Regression] ICE for MVBITS with derived type argument that has run-time subscripts
  2009-01-16 20:47 [Bug fortran/38883] New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts dick dot hendrickson at gmail dot com
                   ` (8 preceding siblings ...)
  2009-01-27 18:10 ` domob at gcc dot gnu dot org
@ 2009-01-29 17:44 ` hjl at gcc dot gnu dot org
  9 siblings, 0 replies; 11+ messages in thread
From: hjl at gcc dot gnu dot org @ 2009-01-29 17:44 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from hjl at gcc dot gnu dot org  2009-01-29 17:43 -------
Subject: Bug 38883

Author: hjl
Date: Thu Jan 29 17:43:14 2009
New Revision: 143765

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=143765
Log:
2009-01-29  H.J. Lu  <hongjiu.lu@intel.com>

        2009-01-28  Richard Guenther  <rguenther@suse.de>

        PR middle-end/38908
        * g++.dg/warn/Wuninitialized-2.C: New testcase.

        2009-01-27  Daniel Kraft  <d@domob.eu>

        PR fortran/38883
        * gfortran.dg/mvbits_6.f90:  New test.
        * gfortran.dg/mvbits_7.f90:  New test.
        * gfortran.dg/mvbits_8.f90:  New test.

        2009-01-21  Daniel Kraft  <d@domob.eu>

        PR fortran/38887
        * gfortran.dg/mvbits_5.f90:  New test.

Added:
    branches/gcc-4_3-branch/gcc/testsuite/g++.dg/warn/Wuninitialized-2.C
      - copied unchanged from r143764,
trunk/gcc/testsuite/g++.dg/warn/Wuninitialized-2.C
    branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/mvbits_5.f90
      - copied unchanged from r143764,
trunk/gcc/testsuite/gfortran.dg/mvbits_5.f90
    branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/mvbits_6.f90
      - copied unchanged from r143764,
trunk/gcc/testsuite/gfortran.dg/mvbits_6.f90
    branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/mvbits_7.f90
      - copied unchanged from r143764,
trunk/gcc/testsuite/gfortran.dg/mvbits_7.f90
    branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/mvbits_8.f90
      - copied unchanged from r143764,
trunk/gcc/testsuite/gfortran.dg/mvbits_8.f90
Modified:
    branches/gcc-4_3-branch/gcc/testsuite/ChangeLog


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38883


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

end of thread, other threads:[~2009-01-29 17:44 UTC | newest]

Thread overview: 11+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-01-16 20:47 [Bug fortran/38883] New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts dick dot hendrickson at gmail dot com
2009-01-16 21:38 ` [Bug fortran/38883] [4.4 Regression] " burnus at gcc dot gnu dot org
2009-01-16 21:43 ` jakub at gcc dot gnu dot org
2009-01-16 21:47 ` mikael at gcc dot gnu dot org
2009-01-18 14:28 ` [Bug fortran/38883] [4.4 Regression] ICE " burnus at gcc dot gnu dot org
2009-01-18 19:16 ` burnus at gcc dot gnu dot org
2009-01-20  9:47 ` domob at gcc dot gnu dot org
2009-01-25  8:36 ` domob at gcc dot gnu dot org
2009-01-27 18:08 ` domob at gcc dot gnu dot org
2009-01-27 18:10 ` domob at gcc dot gnu dot org
2009-01-29 17:44 ` hjl at gcc dot gnu dot 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).