!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! MASTER MECHANISM - ROUTINE NAME : rdrad ! ! ! ! PURPOSE: - read the data in xxx.dat files for forced reaction ! ! ! ! INPUT: none ! ! ! ! OUTPUT: ! ! - nkr : nb. of reaction given as input in the file ro.dat ! ! - krct(i,2) : chemical formula of the reactants for reaction i ! ! - kprd(i,3) : the three main species arising from reaction. ! ! - arrh(i,3) : arrhenius parameter corresponding ! ! to the ith reaction ! ! - kcost(i,3) : stochiometric coefficient corresponding to the 3 ! ! main products of the ith reaction ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! SUBROUTINE rdkwrad(filename,nkr,krct,kprd,arrh,kcost) IMPLICIT NONE INCLUDE 'general.h' ! input CHARACTER(LEN=llin) filename ! output CHARACTER(LEN=lfo) krct(mkr,2),kprd(mkr,3) INTEGER nkr REAL arrh(mkr,3),kcost(mkr,3) ! internal INTEGER i,j,n1,n2,n3,n4,n5,n6,n7,n8,n9 CHARACTER(LEN=300) line ! initialize krct(:,:) = ' ' kprd(:,:) = ' ' arrh = 0. kcost = 0. nkr = 0 line = ' ' ! read the known reactions and their associated label ! --------------------------------------------------- ! open the file OPEN (UNIT=10,FILE=filename,STATUS='OLD') ! read data DO i=1,1000 READ (10,'(a)', end=222) line IF (line(1:3).EQ.'END') EXIT IF (line(1:1).EQ.'*') CYCLE n1=INDEX(line,'|') n2=INDEX(line(n1+1:300),'|')+ n1 n3=INDEX(line(n2+1:300),'|')+ n2 n4=INDEX(line(n3+1:300),'|')+ n3 n5=INDEX(line(n4+1:300),'|')+ n4 n6=INDEX(line(n5+1:300),'|')+ n5 n7=INDEX(line(n6+1:300),'|')+ n6 n8=INDEX(line(n7+1:300),'|')+ n7 ! check that the line is correctly formatted IF (n8.eq.0) THEN WRITE(6,*) '--error--, while reading photo.dat' WRITE(6,*) ' missing "|" at line :' WRITE(6,*) line STOP ENDIF nkr= nkr+1 IF (nkr.ge.mkr) THEN WRITE (6,'(a)') '--error--, while reading ro.dat' WRITE (6,'(a)') 'number of reaction greater than mkr' STOP ENDIF krct(nkr,1) = ADJUSTL(line(1:n1-1)) krct(nkr,2) = ADJUSTL(line(n1+1:n2-1)) kprd(nkr,1) = ADJUSTL(line(n3+1:n4-1)) kprd(nkr,2) = ADJUSTL(line(n5+1:n6-1)) kprd(nkr,3) = ADJUSTL(line(n7+1:n8-1)) READ (line(n2+1:n3-1),*,err=444) kcost(nkr,1) READ (line(n4+1:n5-1),*,err=444) kcost(nkr,2) READ (line(n6+1:n7-1),*,err=444) kcost(nkr,3) READ (line(n8+1:300),*,err=444) (arrh(nkr,j),j=1,3) IF (krct(nkr,2)(1:2).eq.'- ') krct(nkr,2)=' ' IF (kprd(nkr,2)(1:2).eq.'- ') kprd(nkr,2)=' ' IF (kprd(nkr,3)(1:2).eq.'- ') kprd(nkr,3)=' ' ! check the formula (if C>1 only) CALL stdchm(krct(nkr,1)) CALL stdchm(krct(nkr,2)) CALL stdchm(kprd(nkr,1)) CALL stdchm(kprd(nkr,2)) CALL stdchm(kprd(nkr,3)) ENDDO CLOSE (10) RETURN 222 WRITE(6,*) '--error222--, while reading ro.dat' WRITE(6,*) 'keyword END not found' STOP 444 WRITE(6,*) '--error444--, while reading ro.dat at line :' WRITE(6,*) line STOP END