public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/35702]  New: internal compiler error: structure character element with subscripts
@ 2008-03-26  1:06 dick dot hendrickson at gmail dot com
  2008-03-26  6:23 ` [Bug fortran/35702] [4.4, 4.3 regression]: " pault at gcc dot gnu dot org
                   ` (7 more replies)
  0 siblings, 8 replies; 9+ messages in thread
From: dick dot hendrickson at gmail dot com @ 2008-03-26  1:06 UTC (permalink / raw)
  To: gcc-bugs

The following program produces an internal compiler error.
Changing the structure element to real or replacing the
structure subscripts with constants "fixes" the problem.

      MODULE TESTS
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]
! cg0028.f:15: internal compiler error: in gfc_add_modify, at
fortran/trans.c:167


      TYPE UNSEQ


        CHARACTER(1)            ::  C
!        real                   ::  C             !works

      END TYPE UNSEQ       
      CONTAINS
      SUBROUTINE CG0028(TDA1L,TDA1R,nf0,nf1,nf2,nf3)
      TYPE(UNSEQ) TDA1L(NF3)
      TYPE(UNSEQ) TDA1R(NF3)

      TDA1L(NF1:NF2:NF1)%C = TDA1L(NF0+2:NF3:NF2/2)%C

!      TDA1L(1:2:1)%C = TDA1L(0+2:3:2/2)%C               !works

      END SUBROUTINE
      END MODULE TESTS


-- 
           Summary: internal compiler error: structure character element
                    with 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=35702


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

* [Bug fortran/35702] [4.4, 4.3 regression]: structure character element with subscripts
  2008-03-26  1:06 [Bug fortran/35702] New: internal compiler error: structure character element with subscripts dick dot hendrickson at gmail dot com
@ 2008-03-26  6:23 ` pault at gcc dot gnu dot org
  2008-03-26  6:35 ` pault at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-03-26  6:23 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from pault at gcc dot gnu dot org  2008-03-26 06:22 -------
Reddduced testscase

SUBROUTINE CG0028 (TDA1L, N)
  TYPE UNSEQ
    CHARACTER(1)            ::  C
  END TYPE UNSEQ
  integer :: N
  TYPE(UNSEQ) TDA1L(:)
  TDA1L(:)%C = TDA1L(1:N)%C
END SUBROUTINE

I do not have a gcc-4.2 to hand, so cannot check it.

Confirmed

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
      Known to work|                            |4.1.2
   Last reconfirmed|0000-00-00 00:00:00         |2008-03-26 06:22:59
               date|                            |
            Summary|internal compiler error:    |[4.4, 4.3 regression]:
                   |structure character element |structure character element
                   |with subscripts             |with subscripts


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


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

* [Bug fortran/35702] [4.4, 4.3 regression]: structure character element with subscripts
  2008-03-26  1:06 [Bug fortran/35702] New: internal compiler error: structure character element with subscripts dick dot hendrickson at gmail dot com
  2008-03-26  6:23 ` [Bug fortran/35702] [4.4, 4.3 regression]: " pault at gcc dot gnu dot org
@ 2008-03-26  6:35 ` pault at gcc dot gnu dot org
  2008-03-26 21:39 ` pault at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-03-26  6:35 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from pault at gcc dot gnu dot org  2008-03-26 06:34 -------
(In reply to comment #1)
> Reddduced testscase
> 
> SUBROUTINE CG0028 (TDA1L, N)
    TYPE UNSEQ
      CHARACTER(2)            ::  C
    END TYPE UNSEQ

Changing to CHARACTER (LEN /= 1) "fixes" the problem.

If I would hazard a guess, something is going wrong in
trans-expr.c(gfc_trans_string_copy), where LEN=1 is treated separately. I'll
assign myself, since it looks to be consistent with the time that I have for
gfortran at present.

Cheers

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |pault at gcc dot gnu dot org
                   |dot org                     |
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2008-03-26 06:22:59         |2008-03-26 06:34:39
               date|                            |


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


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

* [Bug fortran/35702] [4.4, 4.3 regression]: structure character element with subscripts
  2008-03-26  1:06 [Bug fortran/35702] New: internal compiler error: structure character element with subscripts dick dot hendrickson at gmail dot com
  2008-03-26  6:23 ` [Bug fortran/35702] [4.4, 4.3 regression]: " pault at gcc dot gnu dot org
  2008-03-26  6:35 ` pault at gcc dot gnu dot org
@ 2008-03-26 21:39 ` pault at gcc dot gnu dot org
  2008-03-27 11:11 ` dominiq at lps dot ens dot fr
                   ` (4 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-03-26 21:39 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from pault at gcc dot gnu dot org  2008-03-26 21:38 -------

> If I would hazard a guess, something is going wrong in
> trans-expr.c(gfc_trans_string_copy), where LEN=1 is treated separately.

Yes, this is correct.  In this particular case, we have:

lhs => (void *) &(*(character(kind=1)[0:][1:1] *) atmp.4.data)[S.5]
rhs => (void *) &(*tda1l.0)[(S.5 + 1) * D.590 + D.578].c[1]{lb: 1 sz: 1}

which will clearly run afoul of the check in trans.c.  Rather than mess around
casting and uncasting the rhs, which I know from experience is a pain in the
posterior, I propose the following:

Index: gcc/fortran/trans-expr.c
===================================================================
*** gcc/fortran/trans-expr.c    (revision 133278)
--- gcc/fortran/trans-expr.c    (working copy)
***************
*** 2857,2864 ****
    if (dlength != NULL_TREE && POINTER_TYPE_P (TREE_TYPE (dest)))
      dsc = gfc_to_single_character (dlen, dest);

!
!   if (dsc != NULL_TREE && ssc != NULL_TREE)
      {
        gfc_add_modify_expr (block, dsc, ssc);
        return;
--- 2840,2848 ----
    if (dlength != NULL_TREE && POINTER_TYPE_P (TREE_TYPE (dest)))
      dsc = gfc_to_single_character (dlen, dest);

!   /* Assign directly if the types are compatible.  */
!   if (dsc != NULL_TREE && ssc != NULL_TREE
!       && TREE_TYPE (dsc) == TREE_TYPE (ssc))
      {
        gfc_add_modify_expr (block, dsc, ssc);
        return;

It does not produce the most efficient code for this case but is guaranteed to
work.  This has just gone on to regtest.

Paul


-- 


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


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

* [Bug fortran/35702] [4.4, 4.3 regression]: structure character element with subscripts
  2008-03-26  1:06 [Bug fortran/35702] New: internal compiler error: structure character element with subscripts dick dot hendrickson at gmail dot com
                   ` (2 preceding siblings ...)
  2008-03-26 21:39 ` pault at gcc dot gnu dot org
@ 2008-03-27 11:11 ` dominiq at lps dot ens dot fr
  2008-03-27 22:27 ` [Bug fortran/35702] [4.3/4.4 Regression]: " rguenth at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: dominiq at lps dot ens dot fr @ 2008-03-27 11:11 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from dominiq at lps dot ens dot fr  2008-03-27 11:10 -------
Works as advertised without regression on i686-apple-darwin9 for 32 and 64 bit
modes.

Thanks for the patch.


-- 


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


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

* [Bug fortran/35702] [4.3/4.4 Regression]: structure character element with subscripts
  2008-03-26  1:06 [Bug fortran/35702] New: internal compiler error: structure character element with subscripts dick dot hendrickson at gmail dot com
                   ` (3 preceding siblings ...)
  2008-03-27 11:11 ` dominiq at lps dot ens dot fr
@ 2008-03-27 22:27 ` rguenth at gcc dot gnu dot org
  2008-03-29  8:12 ` pault at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2008-03-27 22:27 UTC (permalink / raw)
  To: gcc-bugs



-- 

rguenth at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
            Summary|[4.4, 4.3 regression]:      |[4.3/4.4 Regression]:
                   |structure character element |structure character element
                   |with subscripts             |with subscripts
   Target Milestone|---                         |4.3.1


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


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

* [Bug fortran/35702] [4.3/4.4 Regression]: structure character element with subscripts
  2008-03-26  1:06 [Bug fortran/35702] New: internal compiler error: structure character element with subscripts dick dot hendrickson at gmail dot com
                   ` (4 preceding siblings ...)
  2008-03-27 22:27 ` [Bug fortran/35702] [4.3/4.4 Regression]: " rguenth at gcc dot gnu dot org
@ 2008-03-29  8:12 ` pault at gcc dot gnu dot org
  2008-03-29  8:19 ` pault at gcc dot gnu dot org
  2008-03-29  8:21 ` pault at gcc dot gnu dot org
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-03-29  8:12 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from pault at gcc dot gnu dot org  2008-03-29 08:11 -------
Subject: Bug 35702

Author: pault
Date: Sat Mar 29 08:11:02 2008
New Revision: 133710

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=133710
Log:
2008-03-29  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/35698
        * trans-array.c (gfc_array_init_size): Set 'size' zero if
        negative in one dimension.

        PR fortran/35702
        * trans-expr.c (gfc_trans_string_copy): Only assign a char
        directly if the lhs and rhs types are the same.

2008-03-29  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/35698
        * gfortran.dg/allocate_zerosize_3.f: New test.

        PR fortran/35702
        * gfortran.dg/character_assign_1.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/allocate_zerosize_3.f
    trunk/gcc/testsuite/gfortran.dg/character_assign_1.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/35702] [4.3/4.4 Regression]: structure character element with subscripts
  2008-03-26  1:06 [Bug fortran/35702] New: internal compiler error: structure character element with subscripts dick dot hendrickson at gmail dot com
                   ` (5 preceding siblings ...)
  2008-03-29  8:12 ` pault at gcc dot gnu dot org
@ 2008-03-29  8:19 ` pault at gcc dot gnu dot org
  2008-03-29  8:21 ` pault at gcc dot gnu dot org
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-03-29  8:19 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2008-03-29 08:18 -------
Subject: Bug 35702

Author: pault
Date: Sat Mar 29 08:17:36 2008
New Revision: 133711

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=133711
Log:
2008-03-29  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/35698
        * trans-array.c (gfc_array_init_size): Set 'size' zero if
        negative in one dimension.

        PR fortran/35702
        * trans-expr.c (gfc_trans_string_copy): Only assign a char
        directly if the lhs and rhs types are the same.

2008-03-29  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/35698
        * gfortran.dg/allocate_zerosize_3.f: New test.

        PR fortran/35702
        * gfortran.dg/character_assign_1.f90: New test.

Added:
    branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/allocate_zerosize_3.f
    branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/character_assign_1.f90
Modified:
    branches/gcc-4_3-branch/gcc/fortran/ChangeLog
    branches/gcc-4_3-branch/gcc/fortran/trans-array.c
    branches/gcc-4_3-branch/gcc/fortran/trans-expr.c
    branches/gcc-4_3-branch/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/35702] [4.3/4.4 Regression]: structure character element with subscripts
  2008-03-26  1:06 [Bug fortran/35702] New: internal compiler error: structure character element with subscripts dick dot hendrickson at gmail dot com
                   ` (6 preceding siblings ...)
  2008-03-29  8:19 ` pault at gcc dot gnu dot org
@ 2008-03-29  8:21 ` pault at gcc dot gnu dot org
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-03-29  8:21 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from pault at gcc dot gnu dot org  2008-03-29 08:20 -------
Fixed on trunk and 4.3

Paul


-- 

pault at gcc dot gnu dot org changed:

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


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


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

end of thread, other threads:[~2008-03-29  8:21 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-03-26  1:06 [Bug fortran/35702] New: internal compiler error: structure character element with subscripts dick dot hendrickson at gmail dot com
2008-03-26  6:23 ` [Bug fortran/35702] [4.4, 4.3 regression]: " pault at gcc dot gnu dot org
2008-03-26  6:35 ` pault at gcc dot gnu dot org
2008-03-26 21:39 ` pault at gcc dot gnu dot org
2008-03-27 11:11 ` dominiq at lps dot ens dot fr
2008-03-27 22:27 ` [Bug fortran/35702] [4.3/4.4 Regression]: " rguenth at gcc dot gnu dot org
2008-03-29  8:12 ` pault at gcc dot gnu dot org
2008-03-29  8:19 ` pault at gcc dot gnu dot org
2008-03-29  8:21 ` pault 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).