Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

FORMAT/OUTPUT

Status
Not open for further replies.

lililulu

Technical User
Jun 29, 2010
2
PL
Hi, I’ve got a problem with format statement. I have a loop and during each iteration I want to add to the existing file a new column (without deleting the previously written). Can someone help me? In short a I’d like to obtain something like this:

(1 iteration) (2 iteration) (3 iteration)
A1 B1 C1
A2 B2 C2
A3 B3 C3

A1…B1…C3 are double precision, I’m using f77

Thank you very much in advance:)
 
Not so easy to do. This is not a FORMAT problem but a sequential file problem. In particular, I don't know any language or tool able to do that in a simple way.

I suggest a change in your row/column numbering. You should write one row by iteration instead of one column by iteration. This is much easier to implement. And this is the normal way !

Notice that a simple solution exists if the final file is not too big : storing all the results in a matrix and writing the resulting file only at the end. But this works only if all the iterations are done in a single run.

Finally, if you persist in your initial choice, then the solution consists in creating a temporary file and replacing the old file (previous iteration) by the new one at each iteration (very expensive if the file is large).

This is relatively easy to implement that in FORTRAN.

Example in fixed format (almost F77 but I cannot be absolutely sure bacause all my compilers are F95+) :

Code:
      PROGRAM main

      IMPLICIT NONE

      INTEGER nrow,niter
      PARAMETER(nrow=10,niter=5)
      DOUBLE PRECISION a(niter)
      INTEGER iter,i,k,stat
      CHARACTER*500 row

1000  FORMAT(10(1X,1PE12.5))

      OPEN(15,file='result.txt')
      OPEN(16,file='temp.txt')

      DO iter=1,niter
        IF(iter > 1) THEN
          REWIND(15)
          REWIND(16)
        ENDIF
        DO i=1,nrow
CCC       Reading the file 15 only is already created
          IF(iter > 1)
     *    READ(15,1000) (a(k),k=1,iter-1)
CCC       adding the column "iter" in the row "i"
          a(iter) = iter+i
CCC       writing the new row
          WRITE(16,1000) (a(k),k=1,iter)
        ENDDO
CCC     Copying 16 into 15
        IF(iter > 1) REWIND(15)
        REWIND(16)
        DO i=1,nrow
          READ(16,'(A)') row
          WRITE(15,'(A)') row(1:len_trim(row))
        ENDDO
      ENDDO

      END

At last, switch to FORTRAN-95 please. F77 is totally obsolete. And use the free format !


 
Interesting problem. If you find you are spending a lot of time copying files, you could just switch the channel numbers, which, are after all integers. Using FJacqs, solution, it will look something like
Code:
      PROGRAM main

      IMPLICIT NONE

      INTEGER nrow,niter
      PARAMETER(nrow=10,niter=5)
      DOUBLE PRECISION a(niter)
      INTEGER iter,i,k,stat,infile,outfile,total
      CHARACTER*500 row

1000  FORMAT(10(1X,1PE12.5))

      OPEN(15,file='odd.txt')
      OPEN(16,file='even.txt')
      infile = 15
      outfile = 16
      total = infile + outfile

      DO iter=1,niter
!       switch files
        infile = outfile
        outfile = total - infile

        IF(iter > 1) THEN
          REWIND(infile)
          REWIND(outfile)
        ENDIF
        DO i=1,nrow
!         Reading the file 15 only is already created
          IF(iter > 1)  READ(infile,1000) (a(k),k=1,iter-1)
!         adding the column "iter" in the row "i"
          a(iter) = iter+i
!         writing the new row
          WRITE(outfile,1000) (a(k),k=1,iter)
        ENDDO
        
      ENDDO
      if (outfile .eq. 15) then
         print *, 'Result in odd.txt'
      else
         print *, 'Result in even.txt'
      end if
      END
 
Another problem is the number of columns. If the number of columns exceeds 10, then it will wrap to the next line. To avoid this, use a variable format
Code:
      PROGRAM main

      IMPLICIT NONE

      INTEGER nrow,niter
      PARAMETER(nrow=10,niter=12)
      DOUBLE PRECISION a(niter)
      INTEGER iter,i,k,infile,outfile,total
      CHARACTER*32  infmt, outfmt

      OPEN(15,file='odd.txt')
      OPEN(16,file='even.txt')
      infile = 15
      outfile = 16
      total = infile + outfile
      outfmt = '(  1(1X,1PE8.1))'
      DO iter=1,niter
!       switch files
        infile = outfile
        outfile = total - infile
!       set up the formats
        infmt = outfmt
        write (outfmt(2:4), '(I2)') iter

        IF(iter > 1) THEN
          REWIND(infile)
          REWIND(outfile)
        ENDIF
        DO i=1,nrow
!         Reading the file 15 only is already created
          IF(iter > 1)  READ(infile,infmt) (a(k),k=1,iter-1)
!         adding the column "iter" in the row "i"
          a(iter) = iter+i
!         writing the new row
          WRITE(outfile,outfmt) (a(k),k=1,iter)
        ENDDO
        
      ENDDO
      if (outfile .eq. 15) then
         print *, 'Result in odd.txt'
      else
         print *, 'Result in even.txt'
      end if
      END
 
I totally agree with xwb about his proposed improvements of my small example program. And I am sure that it is still possible to improve it.

But I would like to insist again : this solution must be avoided ! Building a file which number of columns varies versus the number of iterations is very bad !

Look at the CSV file format (Comma Separated Variable) which can be read by tools like Excel for instance. The number of columns is always fixed (usually, each column has even a name) and the number of rows may be huge. This form is very suitable for drawing curves with standard graphical tools.

I am almost sure that the CSV file format it much better for you needs.


 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top