!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! ! ! ! ! ! ! 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 compteur(name,chem, & nalde,nalco,nooh,ncooh,ncoooh, & molmass, & malde,malco,mooh,mcooh,mcoooh) IMPLICIT NONE INCLUDE 'general.h' ! input: CHARACTER(LEN=lfo),INTENT(in) :: chem CHARACTER(LEN=lco),INTENT(in) :: name REAL,INTENT(in) :: molmass !input/output INTEGER,INTENT(inout) :: nalde,nalco,nooh,ncooh,ncoooh REAL,INTENT(inout) :: malde,malco,mooh,mcooh,mcoooh ! internal CHARACTER(LEN=lgr) :: group(mca) INTEGER :: bond(mca,mca),nring,dbflg INTEGER :: i,j,k,nc,nca INTEGER :: rjg(mri,2) ! ---------- ! INITIALIZE ! ---------- nc = index(chem,' ') - 1 CALL grbond(chem,nc,group,bond,dbflg,nring) ! IF RINGS EXIST remove ring-join characters from groups IF (nring.gt.0) THEN CALL rjgrm(nring,group,rjg) ENDIF ! count the number of functions nca=0 DO i=1,mca IF (group(i).EQ.' ') EXIT IF (group(i)(1:3).EQ.'CHO') nalde=nalde+1 IF (INDEX(group(i),'CO(OH)').NE.0) THEN ncooh=ncooh+1 ELSE IF (INDEX(group(i),'(OH)').NE.0) THEN nalco=nalco+1 ENDIF IF (INDEX(group(i),'CO(OOH)').NE.0) THEN ncoooh=ncoooh+1 ELSE IF (INDEX(group(i),'(OOH)').NE.0) THEN nooh=nooh+1 ENDIF ENDDO ! add the mass of "functions" IF (INDEX(chem,'CHO').NE.0) malde = malde + molmass IF ((INDEX(chem,'C(OH)').NE.0).OR. & (INDEX(chem,'CH(OH)').NE.0).OR. & (INDEX(chem,'CH2(OH)').NE.0)) THEN malco = malco + molmass ENDIF IF (INDEX(chem,'CO(OH)').NE.0) mcooh = mcooh + molmass IF (INDEX(chem,'(OOH)').NE.0) mooh = mooh + molmass ! write the species in the output files IF (INDEX(chem,'CHO').NE.0) WRITE(84,'(a1,a6)') 'A',name IF (INDEX(chem,'(OOH)').NE.0) WRITE(85,'(a1,a6)') 'A',name IF ((INDEX(chem,'C(OH)').NE.0).OR. & (INDEX(chem,'CH(OH)').NE.0).OR. & (INDEX(chem,'CH2(OH)').NE.0)) THEN WRITE(86,'(a1,a6)') 'A',name ENDIF IF (INDEX(chem,'CO(OH)').NE.0) WRITE(87,'(a1,a6)') 'A',name RETURN END