************************************************************************ * MASTER MECHANISM - ROUTINE NAME : rdhv * * * * PURPOSE: - read the data in photo.dat file (i.e the photolytic * * data for the species used as "reference") * * - read typical J value (at a zenithal angle of 40) * * * * INPUT: none * * * * OUTPUT: * * - jdat : nb. of photolytic reaction given as input in * * the file photo.dat * * - jlabel(i) : ID number of photolytic reaction i * * - jchem(i) : chemical formula of the reactant for reaction i * * - jprod(2,i) : the two main species arising from the photolytic * * bond break. If a third product is formed, then * * it must be stored in coprodj(i) * * - coprodj(i) : additional product in reaction (i) - species * * in coprod are not the organic fragments but * * only minor inorganic coproduct * * - jlab40(i) : label of the ith data for which J value has been * * evaluated (at a zenith angle of 40) * * - j40(i) : J value (at a zenith angle of 40) corresponding * * to the reaction having the label jlab40(i) * ************************************************************************ SUBROUTINE rdhv(jdat,jlabel,jchem,jprod,coprodj,jlab40,j40) IMPLICIT NONE INCLUDE 'general.h' * input : none * output CHARACTER(LEN=lfo) jchem(mkr),jprod(2,mkr) CHARACTER(LEN=lco) coprodj(mkr) INTEGER jdat,jlabel(mkr),jlab40(mkr) REAL j40(mkr) * internal INTEGER i,n1,n2,n3,n4,idat CHARACTER(LEN=200) line * initialize DO i=1,mkr jchem(i)=' ' jlabel(i)=0 jprod(1,i)=' ' jprod(2,i)=' ' coprodj(i)=' ' ENDDO jdat = 0 idat=0 DO i=1,100 j40(i)=0. jlab40(i)=0 ENDDO line = ' ' * read the known reactions and their associated label * --------------------------------------------------- * open the file OPEN (UNIT=10,FILE='../DATA/photo.dat',STATUS='OLD') * read photolysis data DO 10 i=1,1000 READ (10,'(a)', end=222) line IF (line(1:3).EQ.'END') GOTO 20 IF (line(1:1).EQ.'*') GOTO 10 n1=index(line,'|') n2=index(line(n1+1:200),'|')+ n1 n3=index(line(n2+1:200),'|')+ n2 n4=index(line(n3+1:200),'|') * check that the line is correctly formatted IF (n4.eq.0) THEN WRITE(6,*) '--error--, while reading photo.dat' WRITE(6,*) ' missing "|" at line :' WRITE(6,*) line STOP ENDIF n4 = n4 + n3 jdat= jdat+1 IF (jdat.ge.mkr) THEN WRITE (6,'(a)') '--error--, while reading photo.dat' WRITE (6,'(a)') 'number of reaction greater than mkr' STOP ENDIF jchem(jdat) = ADJUSTL(line(1:n1-1)) READ (line(n1+1:n2-1),*,err=444) jlabel(jdat) jprod(1,jdat) = ADJUSTL(line(n2+1:n3-1)) jprod(2,jdat) = ADJUSTL(line(n3+1:n4-1)) coprodj(jdat) = ADJUSTL(line(n4+1:110)) * check the formula (if C>1 only) CALL stdchm(jchem(jdat)) CALL stdchm(jprod(1,jdat)) CALL stdchm(jprod(2,jdat)) IF (coprodj(jdat)(1:2).eq.'- ') coprodj(jdat)=' ' 10 CONTINUE 20 CONTINUE CLOSE (10) * Read the photolysis rates for a 40° zenith angle * --------------------------------------------------- * open the file OPEN (UNIT=10,FILE='../DATA/j40.dat',STATUS='OLD') * 42 photolysis constants are available in 'test40' DO 100 i=1,1000 READ(10,'(a)',end=333) line IF (line(1:3).EQ.'END') GOTO 200 IF (line(1:1).EQ.'*') GOTO 100 idat=idat+1 IF (idat.ge.mkr) THEN WRITE (6,'(a)') '--error--, while reading j40.dat' WRITE (6,'(a)') ' number of data is greater than mkr' STOP ENDIF READ (line,*,err=555) jlab40(idat), j40(idat) 100 CONTINUE 200 CONTINUE CLOSE (10) RETURN 222 WRITE(6,*) '--error222--, while reading photo.dat' WRITE(6,*) 'keyword END not found' STOP 333 WRITE(6,*) '--error333--, while reading j40.dat' WRITE(6,*) 'keyword END not found' STOP 444 WRITE(6,*) '--error444--, while reading photo.dat at line :' WRITE(6,*) line STOP 555 WRITE(6,*) '--error555--, while reading j40.dat at line :' WRITE(6,*) line STOP END