************************************************************************ * MASTER MECHANISM - ROUTINE NAME : rdrate * * * * PURPOSE: - read the rate constant of a given series (e.g. OH+VOC, * * NO3+VOC, ...) * * * * INPUT: * * - filename : name of the file to be read * * * * OUTPUT: * * - ndat : number of data that has been read * * - oxchem : total number of know rate constant with ox * * - oxrate(i,3) : arrhenius parameter of the rate constant * * corresponding to the ith species with ox * ************************************************************************ SUBROUTINE rdrate(filename,ndat,oxchem,oxrate) IMPLICIT NONE INCLUDE 'general.h' * input CHARACTER(LEN=llin) filename * output CHARACTER(LEN=lfo) oxchem(mrd) REAL oxrate(mrd,3) INTEGER ndat * local : CHARACTER*200 line INTEGER i,j,n1,n2 * initialize ndat=0 DO i=1,mrd oxchem(i)=' ' DO j=1,3 oxrate(i,j)=0. ENDDO ENDDO * open the file !OPEN(10,FILE=filename, FORM='FORMATTED',STATUS='OLD') OPEN(10,FILE=filename,STATUS='OLD') * read the data DO 10 j=1,10000 READ (10,'(a)',end=222) line IF (line(1:3).eq.'END') GOTO 20 IF (line(1:1).eq.'*') GOTO 10 * check that the line is correctly formatted n1=index(line,':') IF (n1.eq.0) THEN WRITE (6,'(a)') '--error--, while reading', filename WRITE (6,'(a)') 'in subroutine rdrate' WRITE (6,'(a)') 'character ":" not found in line :' WRITE (6,'(a)') line STOP ENDIF n2=index(line,';') IF (n2.eq.0) THEN WRITE (6,'(a)') '--error--, while reading', filename WRITE (6,'(a)') 'in subroutine rdrate' WRITE (6,'(a)') 'character ";" not found in line :' WRITE (6,'(a)') line STOP ENDIF ndat=ndat+1 IF (ndat.gt.mrd) THEN WRITE (6,'(a)') '--error--, while reading', filename WRITE (6,'(a)') 'in subroutine rdrate' WRITE (6,'(a)') 'ndat is greater than mrd' STOP ENDIF oxchem(ndat)=line(1:n1-1) READ(line(n1+1:n2-1),*,err=333) (oxrate(ndat,i),i=1,3) 10 CONTINUE 20 CONTINUE CLOSE(10) * check that the given species are correctly written DO i=1,ndat CALL stdchm(oxchem(i)) ENDDO * check that the species is only given one time DO i=1,ndat-1 DO j=i+1,ndat IF (oxchem(i).EQ.oxchem(j)) THEN WRITE(6,'(a)') '--error--, while reading', filename WRITE(6,'(a)') 'in subroutine rdrate' WRITE(6,'(a)') 'the species :',oxchem(i) WRITE(6,'(a)') 'was found more than 1 time' STOP ENDIF ENDDO ENDDO RETURN 222 WRITE(6,*) '--error222--, while reading', filename WRITE(6,*) ' in subroutine rdrate' WRITE(6,*) ' , keyword END not found' STOP 333 WRITE(6,*) '--error333--, at line below while reading', filename WRITE(6,*) ' in subroutine rdrate' WRITE(6,*) line STOP END