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

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).