************************************************************************ * MASTER MECHANISM - ROUTINE NAME : rdchemin * * * * PURPOSE: - read the list of primary species for which the chemical * * scheme must be written. * * * * INPUT: * * - filename : name of the file to be read * * - ninorg : number of inorganic species * * - inorglst(j) : list of inorganic species - include the name + * * formula + functional group info * * - nrec : number of species recorded * * - dict(j) : dictionnary line (name + formula + functional * * group info) of species number j * * * * OUTPUT: * * - ninp : number of "primary" species * * - input(i) : table of the primary species * ************************************************************************ SUBROUTINE rdchemin(filename,ninorg,inorglst,dict,nrec, & nspsp,dictsp, & ninp,input) IMPLICIT NONE INCLUDE 'general.h' * input CHARACTER(LEN=llin) filename INTEGER ninorg CHARACTER(LEN=ldi) inorglst(mfn) CHARACTER(LEN=ldi) dict(mni) INTEGER nrec(mca) INTEGER nspsp CHARACTER(LEN=ldi) dictsp(mfn) * output INTEGER ninp CHARACTER(LEN=lfo) input(mps) * local : CHARACTER*200 line CHARACTER(LEN=lfo) chem INTEGER i,j,nc INTEGER ic, io, cnum, onum, ind, srch CHARACTER*19 ctring LOGICAL locheck DATA ctring /'23dlrBCFHNOS().*=- '/ * initialize ninp=0 DO i=1,mps input(i)=' ' ENDDO * open the file !OPEN(10,FILE=filename, FORM='FORMATTED',STATUS='OLD') OPEN(10,FILE=filename,STATUS='OLD') * read the data DO 10 i=1,10000 READ (10,'(a)',end=222) line IF (line(1:3).eq.'END') GOTO 20 IF (line(1:1).eq.'*') CYCLE IF (line(1:1).eq.' ') CYCLE nc=INDEX(line,' ') IF (nc.gt.lfo) THEN WRITE(6,'(a)') '--error-- in the routine rdchemin' WRITE(6,'(a)') 'length of species exceed lfo for :' WRITE(6,'(a)') line(1:nc) STOP ENDIF chem=line(1:nc) * check that the species is "known" in the generator CALL chcksp(ninorg,inorglst, & nrec,dict, & nspsp,dictsp, & chem) * if the species is a special species (must start with #) ... * ----------------------------------------------------------- IF (chem(1:1).EQ.'#') THEN ninp = ninp+1 IF (ninp.gt.mps) THEN WRITE(6,'(a)') '--error-- in the routine rdchemin' WRITE(6,'(a)') 'too many species in input' WRITE(6,'(a)') 'max input species = msp (see general.h)' STOP ENDIF input(ninp) = chem CYCLE * If not a "special species", then must start with a C * -------------------------------------------------------- ELSE IF((chem(1:1).EQ.'C') & .OR.(chem(1:1).EQ.'c') & .OR.(chem(1:4).EQ.'=Cd1') & .OR.(chem(1:2).EQ.'-O') & ) THEN * get the number of group (C) in the molecule ic = cnum(chem,nc) io = onum(chem,nc) ic = ic + io IF (ic.GT.mca) THEN WRITE(6,*) '--error-- in the routine rdchemin' WRITE(6,*) ' reading species with more than mca C' WRITE(6,*) chem STOP ENDIF * if only 1 carbon, jump to the next species IF (ic.EQ.1) CYCLE ninp = ninp+1 IF (ninp.gt.mps) THEN WRITE(6,'(a)') '--error-- in the routine rdchemin' WRITE(6,'(a)') 'too many species in input' WRITE(6,'(a)') 'max input species = msp (see general.h)' STOP ENDIF input(ninp) = chem * If not a "special species", then must start with a C * (only organic species are expected here) ELSE WRITE(6,*) '--error-- in the routine rdchemin' WRITE(6,*) 'chemical name must start with C or #' WRITE(6,*) chem STOP ENDIF 10 CONTINUE 20 CONTINUE CLOSE(10) RETURN * error statements 222 WRITE(6,*) '--error222--, while reading', filename WRITE(6,*) ' in subroutine rdchemin' WRITE(6,*) ' , keyword END not found' STOP END