!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! ! ! DIMERISATION routine ! ! This routine writes reaction of a given species with a aldehyde or ! ! hydroperoxide to form a dimer ! ! ! ! ! INPUT: ! ! - chem : formula[a120] of the species ! ! - name : code[a6] of the species fixed name ! ! - mass : molar mass of the species ! ! - dimtype : type od species which react which chem : ! ! 1 to react with aldehyde, 2 with hydroperoxide ! ! ! ! ! INPUT/OUTPUT ! ! - lodimer : logical to check if dimerisatyion recation was done ! ! ! ! ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! SUBROUTINE dimerisation(lrea,ldic,name,chem,num,mass,dimtype, & lodimer) IMPLICIT NONE INCLUDE 'general.h' ! input: CHARACTER(LEN=lfo),INTENT(in) :: chem CHARACTER(LEN=lco),INTENT(in) :: name INTEGER,INTENT(in) :: lrea,ldic REAL,INTENT(in) :: mass INTEGER,INTENT(in) :: dimtype !input/output INTEGER,INTENT(inout) :: num LOGICAL,INTENT(inout) :: lodimer ! internal CHARACTER(LEN=lgr) :: group(mca) INTEGER :: bond(mca,mca),nring,dbflg INTEGER :: i,j,k,nc,nca INTEGER :: rjg(mri,2) CHARACTER*1 :: a1,a2,a3,a4 CHARACTER(LEN=lco) :: r(3), p(mnp) REAL :: s(mnp),ar1,ar2,ar3,f298,fratio INTEGER :: idreac, nlab REAL :: xlab,folow(3),fotroe(4) REAL :: auxinfo(9) CHARACTER*1 :: charfrom,charto ! ---------- ! 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 nca=0 DO i=1,mca IF (group(i).EQ.' ') EXIT nca=nca+1 ENDDO ! write the dimer species in the dictionary ! WRITE(ldic,'(A1,A6,10X,A1,F6.1,A1)') ! & 'D',name,'/',mass ,'/' WRITE(83,*) 'dimerisation reaction for ',name,' : ',chem(1:80) ! initialize (most not used here) CALL rxinit3(a1,a2,a3,a4,r,s,p,ar1,ar2,ar3, & f298,fratio,idreac,nlab,xlab,folow,fotroe) ! check the type of reaction ! DIM_1 for aldehyde ! DIM_2 for hydroperoxide IF (dimtype.EQ.1) THEN r(2)= 'DIM_1' ELSE IF (dimtype.EQ.2) THEN r(2)= 'DIM_2' ELSE IF (dimtype.EQ.3) THEN r(2)= 'DIM_3' ELSE IF (dimtype.EQ.4) THEN r(2)= 'DIM_4' ELSE WRITE(6,*) 'id of the type of reaction given not possible' ENDIF ! ---- The species reacts with a dimtype species, if any, to form a dimer IF (num.GT.0) THEN r(1)= name p(1)= name s(1) = 1. ar1 = 2.78E-4 ! ar1 = 2.78E-8 ar2 = 0. ar3 = 0. idreac=5 charfrom='A' charto='D' CALL rxwrit_dyn(lrea,r,s,p,ar1,ar2,ar3, & idreac,auxinfo,charfrom,charto) ! num=num-1 lodimer=.true. ENDIF RETURN END