************************************************************************ * MASTER MECHANISM - ROUTINE NAME number * * * * PURPOSE: - Find the number of each possible atom in the specie CHEM, * * e.g. C's, H's, N's, O's, S's, F's, Cl's, Br's, and .'s * * * * * * INPUT: * * - chem : formula of the species for which the number of * * of atom must be counted * * - nc : length of the chemical formula * * * * OUTPUT: * * - ic : number of carbon atoms * * - ih : number of hydrogen atoms * * - in : number of nitrogen atoms * * - io : number of oxygen atoms * * - ir : number of radical indicator * * - is : number of sulfur atoms * * - ifl : number of fluorine atoms * * - ibr : number of bromine atoms * * - icl : number of chlorine atoms * * * ************************************************************************ SUBROUTINE number(chem,nc,ic,ih,in,io,ir,is,ifl,ibr,icl) IMPLICIT NONE INCLUDE 'general.h' * input: CHARACTER(LEN=lfo) chem INTEGER nc * output: INTEGER ic, ih, in, io, ir,is, ifl, ibr, icl * internal: CHARACTER(LEN=lgr) group(mca) INTEGER bond(mca,mca), dbflg INTEGER nring INTEGER i, n CHARACTER(LEN=lfo) tchem ! a copy of chem INTEGER rjs(mri,2) ! ring-join characters INTEGER nca, ipos * initialize * ---------- tchem=chem ifl = 0 ibr = 0 icl = 0 ic = 0 ih = 0 in = 0 io = 0 is = 0 ir = 0 n = 1 ******************************************************************** * the ring joining character might be misleading. They must be removed * before counting. ******************************************************************** * build groups and bonds matrix for the species CALL grbond (tchem,nc,group,bond,dbflg,nring) IF (nring.ne.0) THEN CALL rjsrm(nring,tchem,rjs) ! rm the ring joining character ENDIF * start counting * -------------- i=INDEX(tchem,' ')+1 10 i=i-1 IF (i.LT.1) GOTO 20 IF (tchem(i:i).EQ.'2') n = 2 IF (tchem(i:i).EQ.'3') n = 3 IF (tchem(i:i).EQ.'4') n = 4 IF (tchem(i-1:i).EQ.'Cl') THEN icl = icl + n n = 1 i = i - 1 ELSE IF (tchem(i:i).EQ.'F') THEN ifl = ifl + n n = 1 ELSE IF (tchem(i:i).EQ.'B') THEN ibr = ibr + n n = 1 ELSE IF (tchem(i:i).EQ.'H') THEN ih = ih + n n = 1 ELSE IF (tchem(i:i).EQ.'N') THEN in = in + n n = 1 ELSE IF (tchem(i:i).EQ.'O') THEN io = io + n n = 1 ELSE IF (tchem(i:i).EQ.'S') THEN is = is + 1 n = 1 ELSE IF (tchem(i:i).EQ.'.') THEN ir = ir + n n = 1 ELSE IF (tchem(i:i).EQ.'C'.OR.tchem(i:i).EQ.'c') THEN ic = ic + 1 n = 1 ENDIF GOTO 10 * end of number 20 CONTINUE RETURN END