************************************************************************ * MASTER MECHANISM - ROUTINE NAME : rddict * * * * PURPOSE: - read the species that are not "self generated" by * * the program (e.g. inorganic, C1 species). * * - initialize the "species" tables (dict, namlst) * * * * INPUT: none * * * * OUTPUT: * * - ninorg : number of inorganic species * * - nrec : number of species recorded * * - nrectot : total number of records (not including inorganic) * * - 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 * * - inorglst(j) : list of inorganic species - includes the name + * * formula + functional group info * ************************************************************************ SUBROUTINE rddict(ninorg,nrec,nrectot, & dict,namlst,inorglst,filename) IMPLICIT NONE INCLUDE 'general.h' ! input CHARACTER(LEN=*) filename * output INTEGER ninorg,nrectot,nrec CHARACTER(LEN=ldi) dict(mni) CHARACTER(LEN=lco) namlst(mni) CHARACTER(LEN=ldi) inorglst(mfn) *local CHARACTER(LEN=ldi) line INTEGER i,j INTEGER cnum,onum,nc,nca * initialize nrectot = 0 nrec = 1 ninorg = 0 DO i=1,100 inorglst(i) = ' ' ENDDO DO i=1,mni dict(i)=' ' namlst(i)=' ' ENDDO dict(1)='####################' namlst(1)='######' * read dictionary: pre-sorted by 100-char chemical formula variable, * since it will be searched using a binary tree search * later in the program (see 'srch'): OPEN (10,file='../DATA/singlec_dic.dat',status='OLD') ! & form='FORMATTED') DO 10 i=1,10000 READ(10,'(a)',err=999, END=222) line IF (line(1:1).EQ.'*') GOTO 10 IF (line(1:3).EQ.'END') GOTO 15 * get the number of C and check that it is not greater than 1 nc = index(line(10:130),' ') - 1 nca = cnum(line(10:nc),nc)+onum(line(10:nc),nc) IF (nca.gt.1) THEN WRITE (6,*) '--error--, while reading singlec_dic.dat' WRITE (6,*) ' species having more than 1 C found' WRITE (6,*) line STOP ENDIF * if C1 species, store data in the dict, namlst IF (nca.EQ.1) THEN IF (line(10:10).NE.'C') THEN WRITE (6,*) '-error-, while reading singlec_dic.dat' WRITE (6,*) ' organic species does not start with C' WRITE (6,*) line STOP ENDIF nrec = nrec + 1 IF (nrec.GT.mni) THEN WRITE (6,*) 'error in rddict, number of record exceed mni' STOP ENDIF nrectot = nrectot + 1 dict(nrec) = line namlst(nrec) = line(1:6) * else inorganic species - store data in inorglst ELSE ninorg = ninorg + 1 inorglst(ninorg) = line ENDIF 10 CONTINUE 15 CLOSE(10) RETURN 222 WRITE (6,*) '--error222--, while reading singlec_dic.dat' WRITE (6,*) ' keyword end not found' STOP 999 WRITE (6,*) '--error999--, while reading singlec_dic.dat' STOP END