replica nfl jerseysreplica nfl jerseyssoccer jerseyreplica nfl jerseys forums.silverfrost.com :: View topic - Program to get number of rows from an input data file
forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

Program to get number of rows from an input data file

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General
View previous topic :: View next topic  
Author Message
Ohornish



Joined: 24 Oct 2013
Posts: 4

PostPosted: Thu Oct 24, 2013 11:41 pm    Post subject: Program to get number of rows from an input data file Reply with quote

I have multiple data files with known number of columns (fixed for all files) but unknown number of varying rows. I am trying to write a program that will read an input file and will provide number of rows, n. I attempted to write the code but of course did not work. Any help would be greatly appreciated. Thanks.

Code:
PROGRAM num_rows
IMPLICIT NONE
INTEGER::n,ierr
ierr = 0
OPEN (UNIT=3, FILE=seqfname, STATUS='OLD', ACTION='READ', IOSTAT=ierr)
DO i = 1,n!
READ (3,*,IOSTAT=ierr)xdummy,y(i)
if (ierr /=0) exit
END DO
CLOSE (UNIT = 3)
WRITE(*,*) number_of_rows
END
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2615
Location: Sydney

PostPosted: Fri Oct 25, 2013 12:08 am    Post subject: Reply with quote

You could try something like:
Code:
!This program will read a data file containing two columns and
!write an output data file containing a single column of interest.
PROGRAM readwrite
    IMPLICIT NONE
    INTEGER :: seqnum, nl, mn, nf
    CHARACTER (LEN=11) :: seqfilein
!
    mn = 0   ! max line length
    nf = 0   ! number of valid files
    DO seqnum = 1,999
       WRITE (seqfilein,'(a,I3.3,a)') 'main',seqnum,'.txt'
       CALL READ_WRITE_DATA  (nl, seqfilein)
       if (nl > 0) nf = nf+1
       mn = max (mn, nl)
    END DO
    write (*,*) 'number of files',nf
    write (*,*) 'longest file is',mn
END
 
!&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&a
SUBROUTINE READ_WRITE_DATA (nl, seqfname)
    IMPLICIT NONE
    INTEGER, INTENT(OUT) :: nl
    CHARACTER (LEN=11), INTENT(IN)  :: seqfname
!
    INTEGER :: i,ierr
    REAL*8  :: x, y
    CHARACTER(LEN=11) :: seqfout   
!
    seqfout = seqfname(1:7)//'.dat'                                           
    OPEN (UNIT=11, FILE=seqfname, STATUS='OLD', ACTION='READ', IOSTAT=ierr)
     if (IERR/=0) then
        WRITE (*,*) ' ERROR OPENING ',seqfname
        nl = -1
        return
     end if
!
    OPEN (UNIT=12, FILE=seqfout, STATUS='REPLACE', ACTION='WRITE', IOSTAT=ierr)
     if (IERR/=0) then
        WRITE (*,*) ' ERROR OPENING ',seqfout
        nl = -2
        return
     end if
!
    DO i = 1, huge(i)
       READ  (11,*,IOSTAT=ierr) x, y
       if (ierr /=0) exit
       WRITE (12,'(F5.2)') y
    END DO
    nl = i-1
    WRITE (*,*) seqfname,' has',nl,' lines'
   
    CLOSE (UNIT = 11)
    CLOSE (UNIT = 12)

END SUBROUTINE READ_WRITE_DATA


Updated with better error management


Last edited by JohnCampbell on Fri Oct 25, 2013 1:47 am; edited 2 times in total
Back to top
View user's profile Send private message
Ohornish



Joined: 24 Oct 2013
Posts: 4

PostPosted: Fri Oct 25, 2013 1:08 am    Post subject: Reply with quote

Thanks Mr. Campbell!
This is exactly what I was looking for!
Cheers!
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General All times are GMT + 1 Hour
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group