************************************************************************ * MASTER MECHANISM - ROUTINE NAME : no3add_c6 * * * * * * PURPOSE : * * This subroutine computes the reaction rates for NO3 addition to * * >C=C=O bond (case 6). * * * * * * INPUT: * * - chem : chemical formula * * - group(i) : groups at position (carbon) i * * - bond(i,j) : carbon-carbon bond matrix of chem * * - ncd : number of "Cd" carbon in chem * * - conjug : =1 if conjugated Cd (C=C-C=C), otherwise =0 * * - cdtable(i) : carbon number bearing a "Cd" * * - cdsub(i) : number of -C- substitutant (including -CO-) bonded * * to the Cd corresponding to cdtable(i) * * * * INPUT/OUTPUT * * - nr : number of reaction channel associated with chem * * - flag(i) : flag that active the channel i * * - rno3(i) : reaction rate (298 K) for channel i * * - pchem(i) : the main organic product of reaction channel i. * * - coprod(i,j) : coproducts of reaction channel i * * * ************************************************************************ SUBROUTINE no3add_c6(chem,bond,group,ncd,conjug,cdtable,cdsub, & nr,flag,rno3,pchem,coprod) IMPLICIT NONE INCLUDE 'general.h' INCLUDE 'organic.h' * input: CHARACTER(LEN=lfo) chem INTEGER bond(mca,mca) CHARACTER(LEN=lgr) group(mca) INTEGER ncd, conjug INTEGER cdtable(4),cdsub(4) * input/output INTEGER nr, flag(mnr) CHARACTER(LEN=lfo) pchem(mnr) REAL rno3(mnr) CHARACTER(LEN=lco) coprod(mnr,mca) * internal INTEGER i,j,k INTEGER tbond(mca,mca),nca CHARACTER(LEN=lgr) tgroup(mca), pold, pnew CHARACTER(LEN=lfo) tempkc CHARACTER(LEN=lco) tprod(mca) CHARACTER(LEN=lfo) rdckprod(mca) CHARACTER(LEN=lco) rdcktprod(mca,mca) INTEGER nip,nring REAL sc(mca) CHARACTER(LEN=lsb) :: progname='no3add_c6' CHARACTER(LEN=ler) :: mesg !------------- ! Initialize !------------- tgroup=group tbond=bond nca=0 DO i=1,mca IF (tgroup(i).NE.'') nca=nca+1 ENDDO ********************************************************************* * add NO3 only at carbonyl group ********************************************************************* DO i=1,nca IF(INDEX(group(i),'CdO').NE.0)THEN nr = nr + 1 IF (nr.GT.mnr) THEN mesg = 'too many reactions created for species' CALL errexit(progname,mesg,chem) ENDIF flag(nr) = 1 pold = 'CdO' pnew = acyl CALL swap (group(i),pold,tgroup(i),pnew) DO j=1,mca IF(bond(i,j).EQ.2)THEN tbond(i,j) = 1 tbond(j,i) = 1 IF(INDEX(group(j),'Cd').NE.0) THEN k=INDEX(group(j),' ') tgroup(j)(2:k-1)=group(j)(3:k) ELSE mesg = 'molecule could not be identified:' CALL errexit(progname,mesg,chem) ENDIF k=INDEX(tgroup(j),' ') tgroup(j)(k:k+5)='(ONO2)' ENDIF ENDDO * rebuild, check, and find co-products: CALL rebond(tbond,tgroup,tempkc,nring) CALL radchk(tempkc,rdckprod,rdcktprod,nip,sc) pchem(nr) = rdckprod(1) IF (nip.NE.1) WRITE(6,*) '2 produits hoadd_c6.f' IF (nip.NE.1) STOP coprod(nr,:) = rdcktprod(1,:) * rename CALL stdchm(pchem(nr)) * reset groups: tgroup(i) = group(i) ! set rate constants based on CdH2=CdO rno3(nr)=1.1E-13 ! Seland et al., 1996 ENDIF ENDDO ! exit case 6 RETURN END