Silverfrost Forums

Welcome to our forums

Program is not always executing

25 Oct 2013 11:44 #13223

http://www50.zippyshare.com/v/83838443/file.html

http://www50.zippyshare.com/v/40471505/file.html

I have two above input data files. They have similar number formats. I created following program with two subroutines (learning how to use subroutines), one will read out the name of input data file and number of rows, and the other will create an output file containing second column.

The program can do what I want with main.txt but not with test.text. Can anyone tell me reason what I am missing? Many thanks!

!This program will read single data file containing two columns and 
!write output file containing second column and give the number of rows 

PROGRAM rw_numrows_singlefile 
IMPLICIT NONE 
INTEGER::n 
DOUBLE PRECISION,DIMENSION(11000000)::vdata, nvdata 
!Not sure how to deal with unknown number of rows so choosing a bigger dimension. 

CHARACTER (LEN=11)::seqfilein  
seqfilein = 'main001.txt' 
!DO seqnum = 1,2,1 
!WRITE(seqfilein(5:7),'(I3.3)')seqnum 
WRITE(*,*)seqfilein 
CALL READDATA(vdata,n,seqfilein) 
CALL WRITEDATA(vdata,n,nvdata,seqfilein)  
END 

!&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&a 
SUBROUTINE READDATA(y,n,seqfname) 
IMPLICIT NONE 
INTEGER::i,ierr 
REAL::xdummy 
INTEGER,INTENT(OUT)::n
DOUBLE PRECISION,INTENT(INOUT),DIMENSION(11000000)::y 
CHARACTER(LEN=11),INTENT(IN)::seqfname 
ierr = 0 
OPEN (UNIT=3, FILE=seqfname, STATUS='OLD', ACTION='READ', IOSTAT=ierr) 
DO i = 1,huge(i) 
READ (3,*,IOSTAT=ierr)xdummy,y(i) 
if (ierr /=0) exit 
END DO 
CLOSE (UNIT = 3) 
n = i-1
write(*,*) n
RETURN 
END SUBROUTINE 

!&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&& 
SUBROUTINE WRITEDATA(vdata,n,nvdata,seqfileout) 
   IMPLICIT NONE 
   INTEGER::i,ierr 
    INTEGER,INTENT(IN)::n 
    DOUBLE PRECISION,INTENT(IN),DIMENSION(n)::vdata 
   DOUBLE PRECISION,INTENT(OUT),DIMENSION(n)::nvdata 
    CHARACTER(LEN=11),INTENT(IN)::seqfileout 
    CHARACTER(LEN=11)::seqfout    
   ierr = 0 
   seqfout = seqfileout(1:7)                                           

    OPEN (UNIT=12, FILE=trim(seqfout)//'.dat', STATUS='REPLACE', ACTION='WRITE', IOSTAT=ierr) 
      DO i = 1,n 
    nvdata(i) = vdata(i) 
    WRITE(12,'(F5.2)') nvdata(i) 
    ENDDO      
    CLOSE (UNIT = 12) 
    
RETURN 
END SUBROUTINE 
27 Oct 2013 12:17 #13233

I did not open the site you referenced. you could try the following change then look at the referenced lines of data.

OPEN (UNIT=13, FILE=seqfname, STATUS='OLD', ACTION='READ', IOSTAT=ierr) 
DO i = 1,huge(i) 
  READ (13,*,IOSTAT=ierr)xdummy,y(i) 
  if (ierr < 0) exit
  if (ierr /=0) write (*,*) 'error reading line',i,' error code =',ierr
END DO 
CLOSE (UNIT = 13) 

Note I changed your file number from 3 to 13 ( don't use < 10) If this does not help, the next change is to read each line into a character string read the numbers from the character string, instead of direct from the file, list out the character string if there is an error.

John

CHARACTER(LEN=11),INTENT(IN)::seqfname 
character line*80

OPEN (UNIT=13, FILE=seqfname, STATUS='OLD', ACTION='READ', IOSTAT=ierr)
 if (ierr /=0) then
   write (*,*)  'Error opening file :',seqfname
   n = -1
   return
  end if

DO i = 1,huge(i) 
  READ (13,fmt='(a)',IOSTAT=ierr) line 
   if (ierr /= 0) exit
  READ (line,*,IOSTAT=ierr)xdummy,y(i) 
  if (ierr ==0) cycle
  write (*,*) 'error reading line',i,' error code =',ierr
  write (*,*) 'Line :',trim(line)
END DO 
write (*,*) 'end of file at line',i,' iostat=',ierr
CLOSE (UNIT = 13) 
28 Oct 2013 5:26 #13246

Thanks John, But I was looking for the mistake I made or the problem with my original program.[/code]

28 Oct 2013 10:12 #13247

A problem with your original code is that you were not reporting the error code, which should help with identifying the problem. I suggested to write out the error code and some description of where it occurred. My second point was to store the input line and report it, as that also helps with understanding the problem. When the program just stops, it is often difficult to identify where and why it stoped.

John

29 Oct 2013 1:24 #13249

I looked at file test001.txt. It is not a DOS format file (CR LF), and I don't think it is in UNIX format(LF) either, as it uses only <CR> as an end of line indicator and <HT> as a number seperator. Opening the file with NOTEPAD will show the problem. If you open it with WORDPAD and save it as plain text that should fix the problem.

Basically the file is not in a format compatible with what READ (unit,*) can manage.

John

29 Oct 2013 5:55 #13250

Try this to test the file ! read_char.f95

      CHARACTER file_name*128, c
      INTEGER*4 ic, iostat
      integer*8 count_ic(0:256), n, nc, na, nz, nl
      integer*8 :: one = 1
!
!  Open the text file as transparent
!
      call command_line (file_name)
!
      open (unit   = 11,               &
            file   = file_name,        &
            status = 'OLD',            &
            form   = 'UNFORMATTED',    &
            access = 'TRANSPARENT',    &
            iostat = iostat)
      write (*,2000) 'Opening file ',trim(file_name),' iostat = ',iostat
2000  format (a,a,a,i0)
!
!  Read all characters
!
      count_ic = 0    ! count of each character
      n        = 0
      nl       = 0
      nc       = 0
      na       = 0
      nz       = 0
!
      do
         read (unit=11, iostat=iostat) c
          if (iostat /= 0) exit
!
         n  = n + one
         ic = ichar(c)
         count_ic(ic) = count_ic(ic)+one
!
         select case (ic)
            case (10)
               nl = nl + one         ! 10:LF indicates end of line
            case (13)
               nl = nl + one         ! 13:CR indicates new line
            case (0:9,11,12,14:31)
               nc = nc + one         ! other control characters
            case (32:126)
               na = na + one         ! text character
            case (127:256)
               nz = nz + one         ! other character
            case default
               write (*,*) 'Unrecognised character : ichar =',ic
         end select
      end do
!
      write (*,2001) trim(file_name)
2001  format (/'Count of active characters in file ',a// 'Ichar    C    Char_Count')
2002  format (i5,a5,b'zz,zzz,zzz,zz#',2x,a)       
2003  format (b'zz,zzz,zzz,zz#',a,a)       
2004  format (a,b'zz,zzz,zzz,zz#',a,i0)  

      do ic = 256,0,-1
         if (count_ic(ic) < one) cycle
         if (ic >= 32 .AND. ic < 128) then
            write (*,2002) ic, char(ic), count_ic(ic)
         else
            write (*,2002) ic, ' ', count_ic(ic)
         end if
      end do
!
      write (*,*) ' '
      if (iostat == -1) then
         write (*,2003) n,' characters read from file ',trim(file_name)
      else
         write (*,2004) 'end of file after',n,' characters : IOSTAT = ',iostat
      end if
     
      write (*,2003) na, ' normal text characters 32-126'
      write (*,2003) nl, ' line control characters 10 or 13'
      write (*,2003) nc, ' other control characters 0-31'
      write (*,2003) nz, ' non-printable characters 127-255'
      nl = max (count_ic(10), count_ic(13))
      write (*,2003) nl, ' lines identified if text file'
!
      if ( count_ic(10) /= count_ic(13)) then
         write (*,2000) ' NOTE : Not typical DOS text file'
         if ( count_ic(10) == 0) then
            write (*,2000) '        Only <CR> used for end of line'
         else if ( count_ic(13) == 0) then
            write (*,2000) '        Only <LF> used for end of line'
         else
            write (*,2000) '        Inconsistent <LF> and <CR> count found'
         end if
      end if
!
      end
Please login to reply.