On Windows XP, with SP2, the following program beeps at me
and opens an alert box saying
"a.exe has encountered a problem and needs to close.  
We are sorry for the inconvenience."

and offers to send Microsoft an error report (I declined).

Based on the print statements, it's the write statement that 
is causing the problem.

Changing the zero sized section subscripts from nf4:nf3 to
4:3 does not cure the problem 

      program try_qi0010
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]



      call       QI0010 (  10,   1,   2,   3,   4,  9,   2)
      end

      SUBROUTINE QI0010 (nf10, nf1, nf2, nf3, nf4,nf9, np2)
      CHARACTER(9) BDA(nf10)
      CHARACTER(9) BDA1(nf10), bval

      INTEGER  J_LEN
      bda1(1) = 'x'
      do I = 2,10
      bda1(i) = 'x'//bda1(i-1)
      enddo
      bda = 'unread'

      print *, 'begin inquire'
      INQUIRE(IOLENGTH = J_LEN) BDA1(NF1:NF10:NF2), BDA1(NF4:NF3),
     $                               BDA1(NF2:NF10:NF2)

      print *, 'begin open '
      OPEN (UNIT=48,
     $      STATUS='SCRATCH',
     $      ACCESS='DIRECT',
     $      RECL = j_len,
     $      IOSTAT = ISTAT,
     $      FORM='UNFORMATTED',
     $      ACTION='READWRITE')

      print *, 'begin write '
      WRITE (48,IOSTAT = ISTAT, REC = 3) BDA1(NF1:NF10:NF2),
     $                    BDA1(NF4:NF3), BDA1(NF2:NF10:NF2)
      IF ( ISTAT .NE. 0) then
        print *, istat, ' WRITE FAILED '
        stop
      ENDIF
      ISTAT = -314

      print *, 'begin read '

      READ (48,IOSTAT = ISTAT, REC = NP2+1) BDA(NF1:NF9:NF2),
     $                       BDA(NF4:NF3), BDA(NF2:NF10:NF2)
      IF ( ISTAT .NE. 0) THEN
        print *, istat, ' read FAILED '
        stop
      ENDIF

      print *, 'begin check '
      DO J1 = 1,10
      BVAL = BDA1(J1)
      IF (BDA(J1) .NE. BVAL)
     $ print *, j1 ,BDA(J1),BVAL
  100 ENDDO;
      END SUBROUTINE


-- 
           Summary: run-time abort writing zero sized section to direct
                    access file
           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=35699

Reply via email to