Silverfrost Forums

Welcome to our forums

READ using DIRECT ACCESS problem

29 Jan 2015 11:14 #15526

Hi Group,

I am having problems with the following code, it is creating the run time error ERR IO-09 in the command window, I have indicated in the code were the problem occurs by using a PAUSE statement.

I have also included a segment from the file 'TEMPFILE.REO' which the routine is trying to sequence.

Any assistance would be appreciated.

* FILE: REORDER.FOR
* flip the order of the records
********************************************************************
      SUBROUTINE REORDER(FLE,L,RLEN,UN1,UN2)
      IMPLICIT NONE
      INTEGER NUM_REC,L,UN1,UN2,I1,RLEN
      CHARACTER *(*) FLE
      CHARACTER *80 LN1

      PRINT*,'**** START SUBROUTINE REORDER ****'
      OPEN(UN1,FILE=FLE(:L))
      NUM_REC = 0
      OPEN(UN2,FILE='TEMPFILE.REO')

      LOOP
        READ(UN1,'(A)',END=100)LN1(:RLEN)
        WRITE(UN2,*)LN1(:RLEN)
        NUM_REC = NUM_REC + 1
      ENDLOOP
100   CLOSE(UN1)
      CLOSE(UN2)
*     PRINT*,'NUM_REC=',NUM_REC
      
      OPEN(UN1,FILE='TEMPFILE.REO',FORM='FORMATTED',
     &                        ACCESS='DIRECT',RECL=RLEN)
      OPEN(UN2,FILE=FLE(:L))
      DO I1 = NUM_REC,1,-1

      PAUSE'*** OK TO HERE NEXT LINE CAUSING PROBLEM ***'

        READ(UN1,'(A)',REC=I1)LN1(:RLEN)
        WRITE(UN2,*)LN1(:RLEN)
      ENDDO
      CLOSE(UN1)
      CLOSE(UN2)
      
      PRINT*,'**** END SUBROUTINE REORDER ****'

      RETURN
      END
********************************************************************


02     9.115385     0.620079     9.115385
02     9.461538     0.620079     9.461538
02     9.807692     0.620079     9.807692
02    10.153846     0.620079    10.153846
29 Jan 2015 12:24 #15528

Assuming that you are just reversing the order of the lines in the file, then this should work: L is unnecessary, remove it from the call statement.

* FILE: REORDER.FOR 
* flip the order of the records 
******************************************************************** 
      SUBROUTINE REORDER(FLE,RLEN,UN1,UN2) 
      IMPLICIT NONE 
      INTEGER NUM_REC,UN1,UN2,I1,RLEN 
      CHARACTER *(*) FLE 
      CHARACTER *80 LN1 

      PRINT*,'**** START SUBROUTINE REORDER ****' 
      OPEN(UN1,FILE=trim(FLE) 
      NUM_REC = 0 
      OPEN(UN2,FILE='TEMPFILE.REO',access='direct',recl=80) 

      do 
        READ(UN1,'(A)',END=100)LN1 
        NUM_REC = NUM_REC + 1 
        WRITE(UN2,rec=num_rec)LN1 
      enddo 
100   continue
      rewind(UN1) 
      DO I1 = NUM_REC,1,-1 

        READ(UN2,REC=I1)LN1 
        WRITE(UN1,'(a)')trim(LN1) 
      ENDDO 
      CLOSE(UN1) 
      CLOSE(UN2,status='delete') 
      
      PRINT*,'**** END SUBROUTINE REORDER ****' 

      RETURN 
      END 
********************************************************************

Regards Ian

30 Jan 2015 1:00 #15532

Ian's changes are a good recommendation. You could use a temporary file: OPEN (UN2, STATUS='SCRATCH', IOSTAT=IOSTAT, FORM='UNFORMATTED', ACCESS='DIRECT', RECL=80)

Not sure if CLOSE (UN2, STATUS='DELETE', IOSTAT=IOSTAT) is also required?

I'd also recommend the use of IOSTAT= for the file open and check the returned status.

John

30 Jan 2015 11:03 #15536

John, 'SCRATCH' is a good idea when the code is working, then the status='delete' would not be required. IOSTAT on the open statements is a good idea as well, but then that value should probably be returned to the calling program for it to handle errors. I left out 'UNFORMATTED' as this is the default for direct access. And of course, this can only be used for lines up to 80 characters long. If the lines can be longer or shorter then it would probably run faster if the recl was shorter. I'm not an expert with 'allocate' but that could help. or a work character variable could be allocated in the calling program. The code would then be:

      Character*80 workline
      Character*256 fle

      fle = 'myfile.txt'
.
.
. 
      call reorder(fle,workline,un1,un2,istat)
.
.
      end

* FILE: REORDER.FOR
* flip the order of the records
********************************************************************
      SUBROUTINE REORDER(FLE,workline,UN1,UN2,istat)
      IMPLICIT NONE
      INTEGER NUM_REC,UN1,UN2,I1,RLEN
      CHARACTER *(*) FLE,workline
      rec_len= len(workline)

      OPEN(UN1,FILE=trim(FLE),status='old',iostat=istat)
      if(istat .eq. 0)then
        NUM_REC = 0
        OPEN(UN2, status='scratch', access='direct',
     &          recl=rec_len, iostat=istat)
        if(istat .eq. 0)then
          do
            READ(UN1,'(A)',END=100)LN1
            NUM_REC = NUM_REC + 1
            WRITE(UN2,rec=num_rec)LN1
          enddo
100       continue
          rewind(UN1)
          DO I1 = NUM_REC,1,-1
            READ(UN2,REC=I1)LN1
            WRITE(UN1,'(a)')trim(LN1)
          ENDDO
          CLOSE(UN1)
          CLOSE(UN2)
        endif    
      endif    
 
      RETURN
      END
******************************************************************** 
30 Jan 2015 12:45 #15540

Mike: If your data file is of medium size (100 kB to a few MB), and you have Cygwin or some Unix utilities package such as GOW installed, you do not need to write a program at all. The following command pipeline will do the job:

cat -n reo.txt | sort /r | sed -e 's/^ *[0-9]*//' > reor.txt

Explanation: The **cat **command adds line numbers to the input data file. The **sort **command with the /r option uses those line numbers to reverse the file. The **sed **command removes the line numbers in the reversed file and writes the results to a new file.

Other programs with similar capabilities are perl, ruby, python, etc.

If you need to write a program because you need to do other things with the data that you have not told us about, these days (when memory is fast, cheap and plentiful, and disks are cheap and plentiful but slow) it would be far better to read the entire data file into a buffer, process the data into a second buffer, and output the second buffer to a file. There is no need to write 1960's style programs with direct access files unless you are working with GB size data sets.

Please login to reply.