!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! ! ! ! ! ! ! INPUT: ! ! - rdct : name[a6]+formula[a120] of the species for which ! ! reaction with OH is considered ! ! - bond(i,j) : carbon-carbon bond matrix of chem ! ! - group(i) : groups at position (carbon) i ! ! - level : number of level (stable + radicals) that were ! ! necessary to produce the parent of rdct ! ! - stabl : number of stable level (no radical) that were ! ! necessary to produce the parent of rdct ! ! - nfn : total nb. of species having a fixed name ! ! - namfn(i) : table of the fixed name (6 character) ! ! - chemfn(i) : formula corresponding the ith species having a ! ! fixed name ! ! ! ! INPUT/OUTPUT ! ! - dict(j) : dictionary line (name + formula + functional ! ! group info) of species number j ! ! - namlst(j) : name (lco=6 characters) of the species already ! ! used at position number j ! ! - nhldrad : number of radical in the stack ! ! - holdrad(i) : list of the radicals in the stack ! ! ! ! ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! SUBROUTINE autoox(rdct,bond,group,nring,dict,namlst, & dbrch,nhldvoc,holdvoc,nhldrad,holdrad,level,stabl, & nfn,namfn,chemfn,oxdone) IMPLICIT NONE INCLUDE 'general.h' INCLUDE 'common.h' ! input: CHARACTER(LEN=lcf),INTENT(in) :: rdct CHARACTER(LEN=lgr),INTENT(in) :: group(mca) INTEGER,INTENT(in) :: bond(mca,mca),nring ! input/output CHARACTER(LEN=ldi),INTENT(inout) :: dict(mni) CHARACTER(LEN=lco),INTENT(inout) :: namlst(mni) REAL,INTENT(inout) :: dbrch(mni) INTEGER,INTENT(inout) :: nfn CHARACTER(LEN=lco),INTENT(inout) :: namfn(mfn) CHARACTER(LEN=lfo),INTENT(inout) :: chemfn(mfn) INTEGER,INTENT(inout) :: level INTEGER,INTENT(inout) :: stabl CHARACTER(LEN=lst),INTENT(inout) :: holdvoc(mlv) INTEGER,INTENT(inout) :: nhldvoc CHARACTER(LEN=lst),INTENT(inout) :: holdrad(mra) INTEGER,INTENT(inout) :: nhldrad ! output INTEGER,INTENT(out) :: oxdone ! internal CHARACTER(LEN=lfo) :: pchem(mca), tempkc INTEGER :: i,j,k,nc,nca,cnum,onum,np CHARACTER(LEN=lgr) :: tgroup(mca), pold, pnew INTEGER :: tbond(mca,mca) INTEGER :: nabcde(9), tabcde(9,mco,mca) CHARACTER*1 :: a1, a2, a3, a4 CHARACTER(LEN=lco) :: r(3), p(mnp) REAL :: s(mnp), ar1,ar2,ar3,f298,fratio REAL :: brtio INTEGER :: idreac, nlabel REAL :: xlabel,folow(3),fotroe(4) CHARACTER(LEN=lfo) :: rdckprod(mca) CHARACTER(LEN=lco) :: rdcktprod(mca,mca) INTEGER :: nip,irad REAL :: sc(mca) INTEGER :: rjg(mri,2) ! INTEGER :: ring(mca),rngflg ! =1 if node participates in current ring ! ---------- ! INITIALIZE ! ---------- IF (wtflag.NE.0) write(*,*) '*autoox*' ! IF RINGS EXIST remove ring-join characters from groups ! IF (nring.gt.0) THEN ! CALL rjgrm(nring,group,rjg) ! ENDIF ! count number of carbons + '-O-': nc = INDEX(rdct(lco+1:lcf),' ') - 1 nca = cnum(rdct(lco+1:lcf),nc)+onum(rdct(lco+1:lcf),nc) tgroup = group tbond = bond oxdone = 0 irad = 0 ! Search if the species has the good structure : RO2-C-C-CHO DO i=1,nca IF (INDEX(tgroup(i),'OO.').NE.0) THEN irad = i CALL findring(1,2,nca,tbond,rngflg,ring) IF (ring(irad).EQ.1) RETURN CALL abcde_map(tbond,irad,nca,nabcde,tabcde) EXIT ENDIF ENDDO ! auto oxidation via a membered intermediate : k = number of C in the ! intermediate : e.g : k=2 means R-CH(OO.)CHO -> R-CH(OOH)CO(OO.) with a ! 5 membered intermediate DO k=2,5 IF (oxdone.EQ.0) THEN DO i=1,nabcde(k) j=tabcde(k,i,k) IF (tgroup(j).EQ.'CHO') THEN oxdone = 1 pold = 'OO.' pnew = 'OOH' CALL swap(group(irad),pold,tgroup(irad),pnew) pold = 'CHO' pnew = 'CO(OO.)' CALL swap(group(j),pold,tgroup(j),pnew) CALL rebond(tbond,tgroup,tempkc,nring) CALL radchk(tempkc,rdckprod,rdcktprod,nip,sc) pchem(1) = rdckprod(1) CALL stdchm(pchem(1)) IF (nip.NE.1) STOP 'auto-ox.f' EXIT ENDIF ENDDO ENDIF ENDDO ! if the structure RO2-XX-CHO is not found : EXIT the routine IF (oxdone.EQ.0) RETURN ! write in an output file the reactions WRITE(44,*) rdct(lco+1:lco+100),' -> ',pchem(1) ! ----------- ! WRITE OUT ! ----------- CALL rxinit3(a1,a2,a3,a4,r,s,p,ar1,ar2,ar3, & f298,fratio,idreac,nlabel,xlabel,folow,fotroe) ! we assume that there is 100 % of conversion a1 = rdct(1:1) r(1) = rdct(1:lco) s(1) = 1. ar1 = 1 ar2 = 0 ar3 = 0 f298 = ar1*(298.**ar2)*exp(-ar3/298.) fratio=1. brtio=1 CALL bratio(pchem(1),brtio,p(1), & dbrch,dict,namlst, & nhldvoc,holdvoc,nhldrad,holdrad,level,stabl, & nfn,namfn,chemfn) CALL rxwrit3(17,a1,a2,a3,a4,r,s,p,ar1,ar2,ar3, & f298,fratio,idreac,nlabel,xlabel,folow,fotroe) END