!*********************************************************************** ! This subroutine count the number of alcohol moiety leading to ! intramolecular H bounding thrue a 6 or 5 member ring. Priority ! is given to 6 member ring. A alcohol moiety can only be counted once. !*********************************************************************** SUBROUTINE hydol(ng,group,bond,noh15,noh16) IMPLICIT NONE INCLUDE 'general.h' INCLUDE 'common.h' ! input INTEGER ng CHARACTER(LEN=lgr) group(mca) INTEGER bond(mca,mca) ! output INTEGER noh16,noh15 ! local INTEGER tempoh15, tempoh16 INTEGER nohoh15,nohoh16 INTEGER i,j,k,l,m, i1,i2 INTEGER tohoh15,tohoh16 INTEGER nabcde(9), tabcde(9,mco,mca) INTEGER rngflg ! 0 = 'no', 1 = 'yes' INTEGER ring(mca) ! =1 if node participates in current ring INTEGER tring IF(wtflag.NE.0) PRINT*,"*hydol*" ! initialize noh15=0 noh16=0 nohoh15=0 nohoh16=0 ! start loop - only the H of the hydroxy group (whether ! alkohol or carboxylic) is seek of H bonding DO 234 i=1,ng IF (INDEX(group(i),'(OH)').ne.0) THEN ! OPEN 'OH' IF (INDEX(group(i),'CO(OH)').ne.0) GOTO 234 ! EXCLUDE ACID H tohoh16=0 tohoh15=0 tempoh16=0 tempoh15=0 CALL abcde_map(bond,i,ng,nabcde,tabcde) ! gamma position - H bonding occurs only if the nodes does not ! belong to a cycle DO k=1,nabcde(4) l=tabcde(4,k,4) IF (group(l)(1:3).eq.'-O-') THEN i1=i i2=tabcde(4,k,2) CALL findring(i1,i2,ng,bond,rngflg,ring) tring=0 IF (rngflg.ne.0) THEN DO j=1,4 IF (ring(tabcde(4,k,j)).ne.0) tring=tring+1 ENDDO ENDIF IF (tring.le.2) tempoh16=tempoh16+1 ENDIF ENDDO ! beta position DO k=1,nabcde(3) l=tabcde(3,k,3) i1=i i2=tabcde(3,k,2) CALL findring(i1,i2,ng,bond,rngflg,ring) tring=0 IF (rngflg.ne.0) THEN DO j=1,3 IF (ring(tabcde(3,k,j)).ne.0) tring=tring+1 ENDDO ENDIF IF (tring.le.2) THEN ! exit if nodes belong to the same ring IF (INDEX(group(l),'(ONO2)').NE.0) THEN tempoh16=tempoh16+1 ENDIF IF (INDEX(group(l),'(F)').NE.0) THEN tempoh16=tempoh16+1 ENDIF IF (INDEX(group(l),'(Cl)').NE.0) THEN tempoh16=tempoh16+1 ENDIF IF (INDEX(group(l),'(Br)').NE.0) THEN tempoh16=tempoh16+1 ENDIF IF (INDEX(group(l),'(I)').NE.0) THEN tempoh16=tempoh16+1 ENDIF IF (INDEX(group(l),'(OOH)').NE.0) THEN tempoh16=tempoh16+1 ENDIF IF (INDEX(group(l),'CHO').NE.0) THEN tempoh16=tempoh16+1 ENDIF IF (INDEX(group(l)(1:3),'CO ').NE.0) THEN tempoh16=tempoh16+1 ENDIF IF (INDEX(group(l),'(OH)').NE.0) THEN tempoh16=tempoh16+1 tohoh16=tohoh16+1 ! 2 hydroxy can only make 1 bond ENDIF IF (group(l)(1:3).eq.'-O-') THEN tempoh15=tempoh15+1 ENDIF ENDIF ENDDO ! alpha position DO k=1,nabcde(2) l=tabcde(2,k,2) IF (INDEX(group(l),'(NO2)').NE.0) THEN tempoh16=tempoh16+1 ENDIF IF (INDEX(group(l),'(ONO2)').NE.0) THEN tempoh15=tempoh15+1 ENDIF IF (INDEX(group(l),'(F)').NE.0) THEN tempoh15=tempoh15+1 ENDIF IF (INDEX(group(l),'(Cl)').NE.0) THEN tempoh15=tempoh15+1 ENDIF IF (INDEX(group(l),'(Br)').NE.0) THEN tempoh15=tempoh15+1 ENDIF IF (INDEX(group(l),'(I)').NE.0) THEN tempoh15=tempoh15+1 ENDIF IF (INDEX(group(l),'(OOH)').NE.0) THEN tempoh15=tempoh15+1 ENDIF IF (INDEX(group(l),'CHO').NE.0) THEN tempoh15=tempoh15+1 ENDIF IF (INDEX(group(l)(1:3),'CO ').NE.0) THEN tempoh15=tempoh15+1 ENDIF IF (INDEX(group(l),'(OH)').NE.0) THEN tempoh15=tempoh15+1 tohoh15=tohoh15+1 ENDIF ENDDO ! curent position IF (INDEX(group(i),'(OOH)').NE.0) THEN tempoh15 = tempoh15+1 ENDIF ! analyse H bonds. A given -OH make only one bond. Priority is ! given to 6 member ring, then 5 member ring. Care must be take for ! dihydroxy species, which can only make one H-bond IF (tempoh16.gt.0) THEN noh16=noh16+1 IF ((tohoh16.gt.0).and.(tempoh16.eq.1)) THEN nohoh16=nohoh16+1 ! Hbond exist true dihydroxy group only ENDIF ELSE IF (tempoh15.gt.0) THEN noh15=noh15+1 IF ((tohoh15.gt.0).and.(tempoh15.eq.1)) THEN nohoh15=nohoh15+1 ! Hbond exist true dihydroxy group only ENDIF ENDIF ENDIF 234 CONTINUE nohoh16=nohoh16/2 ! integer division on purpose IF (nohoh16.ne.0) THEN noh16=noh16-nohoh16 ENDIF nohoh15=nohoh15/2 ! integer division on purpose IF (nohoh15.ne.0) THEN noh15=noh15-nohoh15 ENDIF ! return END