public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/34785]  New: internal compiler error for array constructor for sequence type
@ 2008-01-14 22:54 dick dot hendrickson at gmail dot com
  2008-01-14 23:30 ` [Bug fortran/34785] " burnus 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-01-14 22:54 UTC (permalink / raw)
  To: gcc-bugs

I get the message

og0015.f: In function 'og0015':
og0015.f:81: internal compiler error: in gfc_trans_array_constructor, at
fortran
/trans-array.c:1672

I think things work if I replace the "use o_type_defs" with the actual
contents of the module.  (Technically, this one was hard to isolate, so
I might misremember this).

Dick Hendrickson

      MODULE o_TYPE_DEFS

      TYPE SEQ

      SEQUENCE

        REAL(4)                              R, RA(9,10)
        REAL(8)                          ::  D, DA(1:10)
        REAL(10)                              Q
        REAL(KIND=10), DIMENSION(10)      ::  QA

        COMPLEX(4)                       ::  Z, ZA(0:8,1-1:9)
        COMPLEX(KIND=8), DIMENSION (20)  ::  YA(10)
        COMPLEX(8)                       ::  Y
        COMPLEX(10)                       ::  X, XA(-4:5)

        CHARACTER(9,1)                   ::  B, BA(-4:5)
        INTEGER(4)                       ::  I, IA(9,10)
        INTEGER(KIND=4)                  ::  H
        CHARACTER(1,KIND=1)            ::  C, CA(9,10)
        INTEGER(4), DIMENSION(10)        ::  HA(-4:5)

        CHARACTER(LEN=9,KIND=1)          ::  E, EA(9,10)
        LOGICAL(4)                       ::  L, LA(9,10)
        CHARACTER(KIND=1)                    F, FA(10)
        LOGICAL(4)                       ::  G, GA(10)

      END TYPE SEQ

! TEMPORARIES FOR USE WITH 'SEQ' AND 'UNSEQ' TYPES
        REAL(4)                          ::  RS_T, RA_T(9,10)
        REAL(8)                          ::  DS_T, DA_T(1:10)
        REAL(KIND=10)                     ::  QS_T, QA_T(10)

        COMPLEX(4)                       ::  ZS_T, ZA_T(0:8,0:9)
        COMPLEX(KIND=8)                  ::  YS_T, YA_T(10)
        COMPLEX(10)                       ::  XS_T, XA_T(-4:5)

        INTEGER(4)                       ::  IS_T, IA_T(9,10)
        INTEGER(4)                       ::  HS_T, HA_T(-4:5)

        LOGICAL(4)                       ::  LS_T, LA_T(9,10)
        LOGICAL(4)                       ::  GS_T, GA_T(10)

        CHARACTER(9,1)                   ::  BS_T, BA_T(-4:5)
        CHARACTER(1,KIND=1)            ::  CS_T, CA_T(9,10)
        CHARACTER(LEN=9,KIND=1)          ::  ES_T, EA_T(9,10)
        CHARACTER(KIND=1, LEN=5-4)   ::  FS_T, FA_T(10)

      END MODULE o_TYPE_DEFS


      MODULE TESTS
!  COPYRIGHT 1999   SPACKMAN & HENDRICKSON, INC.

      use o_type_defs

!      INTEGER, PRIVATE :: J1,J2,J3,J4,J5,J6,J7,JJJ
      CONTAINS
      SUBROUTINE OG0015(UDS0L)
!  COPYRIGHT 1999   SPACKMAN & HENDRICKSON, INC.
      TYPE(SEQ)          UDS0L

      UDS0L = SEQ(INT(RS_T),INT(RESHAPE((/((RA_T(J1,J2), J1 = 1,9),
     $                         J2=1,10)/), (/9,10/))),
     $            INT(DS_T),INT((/ (DA_T(J1),J1=1,10,1) /)),
     $            INT(QS_T),INT((/ (QA_T(J1), J1=10,1,-1) /)),
     $            ZS_T,RESHAPE( (/ ((ZA_T(J1,J2), J1 =0,8),
     $                         J2=0,9)/),(/9,10/)),
     $            (/ (YA_T(J1),J1=1,2*5,2-1)/),YS_T,
     $            XS_T,(/ (XA_T(J1),J1=-4, 5) /),
     $            BS_T,(/ (BA_T(J1),J1=-4, 5) /),
     $    INT(IS_T),INT(RESHAPE( (/ ((IA_T(J1,J2), J1 =1*1,3*3)
     $            ,J2= 1, 10)/), (/3*3,2*5/))), INT(HS_T),
     $            CS_T,RESHAPE ( (/ ((CA_T(J1,J2), J1 =1, 9,1),
     $                           J2=1, 2*5)/),(/8+1, 10/)),
     $            INT((/ (HA_T(J1), J1=-4,5) /)),
     $            ES_T,EA_T(1:9,1:10),
     $            LS_T,RESHAPE( (/ ((LA_T(J1,J2),J1 = 2-1,10-1),
     $                           J2=2-1,9+1)/), (/9, 10/) ),
     $            FS_T,(/ (FA_T(J1), J1=1,2*5) /),
     $            GS_T,(/ (GA_T(J1), J1= 1*1,2*5) /))

      END SUBROUTINE
      END MODULE TESTS


-- 
           Summary: internal compiler error for array constructor for
                    sequence type
           Product: gcc
           Version: 4.3.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=34785


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

* [Bug fortran/34785] internal compiler error for array constructor for sequence type
  2008-01-14 22:54 [Bug fortran/34785] New: internal compiler error for array constructor for sequence type dick dot hendrickson at gmail dot com
@ 2008-01-14 23:30 ` burnus at gcc dot gnu dot org
  2008-01-15  0:11 ` burnus at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: burnus at gcc dot gnu dot org @ 2008-01-14 23:30 UTC (permalink / raw)
  To: gcc-bugs



-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
OtherBugsDependingO|                            |32834
              nThis|                            |
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
           Keywords|                            |ice-on-valid-code
   Last reconfirmed|0000-00-00 00:00:00         |2008-01-14 22:43:48
               date|                            |


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


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

* [Bug fortran/34785] internal compiler error for array constructor for sequence type
  2008-01-14 22:54 [Bug fortran/34785] New: internal compiler error for array constructor for sequence type dick dot hendrickson at gmail dot com
  2008-01-14 23:30 ` [Bug fortran/34785] " burnus at gcc dot gnu dot org
@ 2008-01-15  0:11 ` burnus at gcc dot gnu dot org
  2008-01-16  9:14 ` pault at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: burnus at gcc dot gnu dot org @ 2008-01-15  0:11 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from burnus at gcc dot gnu dot org  2008-01-14 23:04 -------
The failing assert is:

      /* Complex character array constructors should have been taken care of
         and not end up here.  */
      gcc_assert (ss->string_length);

Reduced test:

      MODULE o_TYPE_DEFS
        implicit none
        TYPE SEQ
          SEQUENCE
          CHARACTER(9,1) ::  BA(-4:5)
        END TYPE SEQ
        CHARACTER(9,1)   ::  BA_T(-4:5)
      END MODULE o_TYPE_DEFS

      MODULE TESTS
        use o_type_defs
        implicit none
      CONTAINS
        SUBROUTINE OG0015(UDS0L)
          TYPE(SEQ)          UDS0L
          integer :: j1
          UDS0L = SEQ((/ (BA_T(J1),J1=-4, 5) /))
        END SUBROUTINE
      END MODULE TESTS


-- 


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


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

* [Bug fortran/34785] internal compiler error for array constructor for sequence type
  2008-01-14 22:54 [Bug fortran/34785] New: internal compiler error for array constructor for sequence type dick dot hendrickson at gmail dot com
  2008-01-14 23:30 ` [Bug fortran/34785] " burnus at gcc dot gnu dot org
  2008-01-15  0:11 ` burnus at gcc dot gnu dot org
@ 2008-01-16  9:14 ` pault at gcc dot gnu dot org
  2008-01-17 17:00 ` pault at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-01-16  9:14 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from pault at gcc dot gnu dot org  2008-01-16 08:00 -------
(In reply to comment #1)
It is sufficient that BA_T is referenced in tests; eg. by PRINT *, BA_T for the
problem to go away.  Thus the problem is that the symbol is not being set as
referenced.  I will try to find out why but will first set it referenced in
gfc_resolve_variable.

Cheers

Paul


-- 


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


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

* [Bug fortran/34785] internal compiler error for array constructor for sequence type
  2008-01-14 22:54 [Bug fortran/34785] New: internal compiler error for array constructor for sequence type dick dot hendrickson at gmail dot com
                   ` (2 preceding siblings ...)
  2008-01-16  9:14 ` pault at gcc dot gnu dot org
@ 2008-01-17 17:00 ` pault at gcc dot gnu dot org
  2008-01-18  9:34 ` pault at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-01-17 17:00 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from pault at gcc dot gnu dot org  2008-01-17 15:33 -------
I have a fix for this that I will apply as "obvious" overnight (in the EU, that
is:))

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-01-14 22:43:48         |2008-01-17 15:33:10
               date|                            |


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


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

* [Bug fortran/34785] internal compiler error for array constructor for sequence type
  2008-01-14 22:54 [Bug fortran/34785] New: internal compiler error for array constructor for sequence type dick dot hendrickson at gmail dot com
                   ` (3 preceding siblings ...)
  2008-01-17 17:00 ` pault at gcc dot gnu dot org
@ 2008-01-18  9:34 ` pault at gcc dot gnu dot org
  2008-01-18 11:28 ` pault at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-01-18  9:34 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from pault at gcc dot gnu dot org  2008-01-18 09:22 -------
(In reply to comment #3)
> I have a fix for this that I will apply as "obvious" overnight (in the EU, that
> is:))
> Paul
....except that it caused a FAIL on one platform and, on another, the testsuite
hung!!!  Anyway, it's on the right track and I'll try and sort it out this
weekend:

gfc_check_constructor_type (gfc_expr *e)
{
  try t;

  cons_state = CONS_START;
  gfc_clear_ts (&constructor_ts);
  gfc_clear_ts (&e->ts);                  /* Fixes this bug. */

  t = check_constructor_type (e->value.constructor);
  if (t == SUCCESS && e->ts.type == BT_UNKNOWN)
    e->ts = constructor_ts;

  return t;
}

Paul


-- 


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


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

* [Bug fortran/34785] internal compiler error for array constructor for sequence type
  2008-01-14 22:54 [Bug fortran/34785] New: internal compiler error for array constructor for sequence type dick dot hendrickson at gmail dot com
                   ` (4 preceding siblings ...)
  2008-01-18  9:34 ` pault at gcc dot gnu dot org
@ 2008-01-18 11:28 ` pault at gcc dot gnu dot org
  2008-01-20  8:53 ` pault at gcc dot gnu dot org
  2008-01-20  9: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-01-18 11:28 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from pault at gcc dot gnu dot org  2008-01-18 09:33 -------
(In reply to comment #4)
Sorry, the above is the fix for PR34784.

This one is fixed by:

In trans-array.c (gfc_add_loop_ss_code)

        case GFC_SS_CONSTRUCTOR:
          if (ss->expr->ts.type == BT_CHARACTER
                && ss->string_length == NULL)
            get_array_ctor_all_strlen (&loop->pre, ss->expr,
                                       &ss->string_length);
          gfc_trans_array_constructor (loop, ss);
          break;

Paul


-- 


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


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

* [Bug fortran/34785] internal compiler error for array constructor for sequence type
  2008-01-14 22:54 [Bug fortran/34785] New: internal compiler error for array constructor for sequence type dick dot hendrickson at gmail dot com
                   ` (5 preceding siblings ...)
  2008-01-18 11:28 ` pault at gcc dot gnu dot org
@ 2008-01-20  8:53 ` pault at gcc dot gnu dot org
  2008-01-20  9: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-01-20  8:53 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2008-01-20 08:23 -------
Subject: Bug 34785

Author: pault
Date: Sun Jan 20 08:22:56 2008
New Revision: 131675

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

        PR fortran/34784
        * array.c (gfc_check_constructor_type): Clear the expression ts
        so that the checking starts from the deepest level of array
        constructor.
        * primary.c (match_varspec): If an unknown type is changed to
        default character and the attempt to match a substring fails,
        change it back to unknown.

        PR fortran/34785
        * trans-array.c (gfc_add_loop_ss_code) : If ss->string_length is
        NULL for an array constructor, use the cl.length expression to
        build it.
        (gfc_conv_array_parameter): Change call to gfc_evaluate_now to
        a tree assignment.


2008-01-20  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/34784
        * gfortran.dg/array_constructor_20.f90: New test.
        * gfortran.dg/mapping_2.f90: Correct ubound expression for h4.

        PR fortran/34785
        * gfortran.dg/array_constructor_21.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/array_constructor_20.f90
    trunk/gcc/testsuite/gfortran.dg/array_constructor_21.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/array.c
    trunk/gcc/fortran/primary.c
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/34785] internal compiler error for array constructor for sequence type
  2008-01-14 22:54 [Bug fortran/34785] New: internal compiler error for array constructor for sequence type dick dot hendrickson at gmail dot com
                   ` (6 preceding siblings ...)
  2008-01-20  8:53 ` pault at gcc dot gnu dot org
@ 2008-01-20  9: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-01-20  9:21 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from pault at gcc dot gnu dot org  2008-01-20 08:44 -------
Fixed on trunk

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=34785


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

end of thread, other threads:[~2008-01-20  8:45 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-01-14 22:54 [Bug fortran/34785] New: internal compiler error for array constructor for sequence type dick dot hendrickson at gmail dot com
2008-01-14 23:30 ` [Bug fortran/34785] " burnus at gcc dot gnu dot org
2008-01-15  0:11 ` burnus at gcc dot gnu dot org
2008-01-16  9:14 ` pault at gcc dot gnu dot org
2008-01-17 17:00 ` pault at gcc dot gnu dot org
2008-01-18  9:34 ` pault at gcc dot gnu dot org
2008-01-18 11:28 ` pault at gcc dot gnu dot org
2008-01-20  8:53 ` pault at gcc dot gnu dot org
2008-01-20  9: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).