! $Id: nucleation_tstep_mod.F90 5105 2024-07-23 17:14:34Z fairhead $ MODULE nucleation_tstep_mod CONTAINS SUBROUTINE nucleation_rate(rhoa,t_seri,pplay,rh,a_xm,b_xm,c_xm,nucl_rate,ntot_n,x_n) USE aerophys USE infotrac_phy USE strataer_local_var_mod, ONLY: flag_new_nucl USE lmdz_yomcst IMPLICIT NONE ! input variables REAL rhoa ! H2SO4 number density [molecules/cm3] REAL t_seri ! temperature (K) REAL pplay ! pressure (Pa) REAL rh ! relative humidity (between 0 and 1) REAL a_xm, b_xm, c_xm ! output variables REAL nucl_rate REAL ntot_n ! total number of molecules in the critical cluster for neutral nucleation REAL x_n ! mole fraction of H2SO4 in the critical cluster for neutral nucleation ! local variables REAL jnuc_n ! nucleation rate in 1/cm3s (10^-7-10^10 1/cm3s) for neutral nucleation REAL rc_n ! radius of the critical cluster in nm for neutral nucleation REAL na_n ! sulfuric acid molecules in the neutral critical cluster (NOT IN USE) LOGICAL kinetic_n ! true if kinetic neutral nucleation (NOT IN USE) LOGICAL kinetic_i ! true if kinetic ion-induced nucleation (NOT IN USE) REAL VH2SO4mol REAL ntot_i, x_i, jnuc_i, rc_i, na_i, n_i ! quantities for charged nucleation (NOT IN USE) REAL csi ! Ion condensation sink (s-1) NOT IN USE REAL airn ! Air molecule concentration in (cm-3) NOT IN USE REAL ipr ! Ion pair production rate (cm-3 s-1) NOT IN USE ! CALL nucleation routine IF (.NOT.flag_new_nucl) THEN ! Use older routine from Hanna Vehkamäki (FMI) CALL binapara(t_seri,rh,rhoa,jnuc_n,x_n,ntot_n,rc_n) ! when total number of molecules is too small ! then set jnuc_n to collision rate of two H2SO4 molecules (following personal communication of Ulrike Niemeier and Hanna Vehkamäki) IF (ntot_n < 4.0) THEN VH2SO4mol=mH2SO4mol/(1.E-3*(a_xm+t_seri*(b_xm+t_seri*c_xm))) !cm3 jnuc_n = rhoa**2. *(3./4.*RPI)**(1./6.) *(12.*RKBOL*t_seri/mH2SO4mol)**0.5 & *100.*(2.*VH2SO4mol**(1./3.))**2. !1/(cm3s) ntot_n=2.0 x_n=1.0 ENDIF ELSE ! Use new routine from Anni Maattanen (LATMOS) csi=0.0 ! no charged nucleation for now ipr=-1.0 ! dummy value to make sure charged nucleation does not occur airn=0.0 ! NOT IN USE ! airn=pplay/t_seri/RD/1.E3*RNAVO/RMD ! molec cm-3 (for future use, to be confirmed) CALL newbinapara(t_seri,rh,rhoa,csi,airn,ipr,jnuc_n,ntot_n,jnuc_i,ntot_i, & x_n,x_i,na_n,na_i,rc_n,rc_i,n_i,kinetic_n,kinetic_i) ENDIF ! convert jnuc_n from particles/cm3/s to kg(H2SO4)/kgA/s nucl_rate=jnuc_n*ntot_n*x_n*mH2SO4mol/(pplay/t_seri/RD/1.E6) END SUBROUTINE nucleation_rate !-------------------------------------------------------------------------------------------------- SUBROUTINE nucleation_part(nucl_rate,ntot,x,dt,tr_seri) USE aerophys USE infotrac_phy USE strataer_local_var_mod, ONLY: Vbin IMPLICIT NONE ! input variable REAL nucl_rate REAL ntot ! total number of molecules in the critical cluster REAL x ! mole raction of H2SO4 in the critical cluster REAL dt ! output variable REAL tr_seri(nbtr) ! local variable INTEGER k REAL Vnew REAL ff(nbtr_bin) ! dry volume of nucleated particle (at reference temperature) ! dens_aer_dry (density of dry aerosol []kg/m3) ! H2SO4mol: mass of an H2SO4 molecule [kg] ! Vnew [m3] Vnew=mH2SO4mol*ntot*x/dens_aer_dry ! compute distribution factor for particles of intermediate size (from Jacobson 1994, equation 13) ff(:)=0.0 DO k=1, nbtr_bin ! CK 20160531: bug fix for first bin IF (k<=nbtr_bin-1) THEN IF (Vbin(k)<=Vnew.AND.Vnew1) THEN IF (Vbin(k-1)=Vbin(k)) THEN ff(k)= 1. ENDIF ENDDO ! correction of ff for volume conservation DO k=1, nbtr_bin ff(k)=ff(k)*Vnew/Vbin(k) ENDDO ! add nucleated H2SO4 to corresponding aerosol bin DO k=1, nbtr_bin tr_seri(k+nbtr_sulgas)=tr_seri(k+nbtr_sulgas)+nucl_rate*dt/(mH2SO4mol*ntot*x)*ff(k) ENDDO END SUBROUTINE nucleation_part !--------------------------------------------------------------------------------------------------- SUBROUTINE binapara(pt,prh,rhoa_in,jnuc,x,ntot,rc) ! Fortran 90 SUBROUTINE binapara ! Calculates parametrized values of nucleation rate, ! mole fraction of sulphuric acid ! total number of particles, and the radius of the critical cluster ! in H2O-H2SO4 system IF temperature, saturatio ratio of water and ! sulfuric acid concentration are given. ! Copyright (C) 2002 Hanna Vehkamäki ! Division of Atmospheric Sciences ! Department of Physical Sciences ! P.O. Box 64 ! FIN-00014 University of Helsinki ! Finland ! hanna.vehkamaki@helsinki.fi IMPLICIT NONE REAL :: pt,t !temperature in K (190.15-300.15K) REAL :: prh,rh !saturation ratio of water (0.0001-1) REAL,INTENT(IN) :: rhoa_in !sulfuric acid concentration in 1/cm3 (10^4-10^11 1/cm3) REAL,INTENT(OUT) :: jnuc !nucleation rate in 1/cm3s (10^-7-10^10 1/cm3s) REAL,INTENT(OUT) :: ntot !total number of molecules in the critical cluster (ntot>4) REAL,INTENT(OUT) :: x ! mole fraction of H2SO4 in the critical cluster REAL,INTENT(OUT) :: rc !radius of the critical cluster in nm REAL :: rhotres ! threshold concentration of h2so4 (1/cm^3) ! which produces nucleation rate 1/(cm^3 s) as a function of rh and t REAL rhoa ! CK: use intermediate variable to avoid overwriting t=pt rh=prh rhoa=rhoa_in IF (t < 190.15) THEN t=190.15 ENDIF IF (t > 300.15) THEN t=300.15 ENDIF IF (rh < 0.0001) THEN rh=0.0001 ENDIF IF (rh > 1.0) THEN rh=1.0 ENDIF IF (rhoa < 1.e4) THEN rhoa=1.e4 ENDIF IF (rhoa > 1.e11) THEN rhoa=1.e11 ENDIF x= 0.7409967177282139 - 0.002663785665140117*t + 0.002010478847383187*LOG(rh) & - 0.0001832894131464668*t*LOG(rh) + 0.001574072538464286*LOG(rh)**2 & - 0.00001790589121766952*t*LOG(rh)**2 + 0.0001844027436573778*LOG(rh)**3 & - 1.503452308794887E-6*t*LOG(rh)**3 - 0.003499978417957668*LOG(rhoa) & + 0.0000504021689382576*t*LOG(rhoa) jnuc= 0.1430901615568665 + 2.219563673425199*t - 0.02739106114964264*t**2 + & 0.00007228107239317088*t**3 + 5.91822263375044/x + & 0.1174886643003278*LOG(rh) + 0.4625315047693772*t*LOG(rh) - & 0.01180591129059253*t**2*LOG(rh) + & 0.0000404196487152575*t**3*LOG(rh) + (15.79628615047088*LOG(rh))/x - & 0.215553951893509*LOG(rh)**2 - 0.0810269192332194*t*LOG(rh)**2 + & 0.001435808434184642*t**2*LOG(rh)**2 - & 4.775796947178588E-6*t**3*LOG(rh)**2 - & (2.912974063702185*LOG(rh)**2)/x - 3.588557942822751*LOG(rh)**3 + & 0.04950795302831703*t*LOG(rh)**3 - & 0.0002138195118737068*t**2*LOG(rh)**3 + & 3.108005107949533E-7*t**3*LOG(rh)**3 - & (0.02933332747098296*LOG(rh)**3)/x + & 1.145983818561277*LOG(rhoa) - & 0.6007956227856778*t*LOG(rhoa) + & 0.00864244733283759*t**2*LOG(rhoa) - & 0.00002289467254710888*t**3*LOG(rhoa) - & (8.44984513869014*LOG(rhoa))/x + & 2.158548369286559*LOG(rh)*LOG(rhoa) + & 0.0808121412840917*t*LOG(rh)*LOG(rhoa) - & 0.0004073815255395214*t**2*LOG(rh)*LOG(rhoa) - & 4.019572560156515E-7*t**3*LOG(rh)*LOG(rhoa) + & (0.7213255852557236*LOG(rh)*LOG(rhoa))/x + & 1.62409850488771*LOG(rh)**2*LOG(rhoa) - & 0.01601062035325362*t*LOG(rh)**2*LOG(rhoa) + & 0.00003771238979714162*t**2*LOG(rh)**2*LOG(rhoa) + & 3.217942606371182E-8*t**3*LOG(rh)**2*LOG(rhoa) - & (0.01132550810022116*LOG(rh)**2*LOG(rhoa))/x + & 9.71681713056504*LOG(rhoa)**2 - & 0.1150478558347306*t*LOG(rhoa)**2 + & 0.0001570982486038294*t**2*LOG(rhoa)**2 + & 4.009144680125015E-7*t**3*LOG(rhoa)**2 + & (0.7118597859976135*LOG(rhoa)**2)/x - & 1.056105824379897*LOG(rh)*LOG(rhoa)**2 + & 0.00903377584628419*t*LOG(rh)*LOG(rhoa)**2 - & 0.00001984167387090606*t**2*LOG(rh)*LOG(rhoa)**2 + & 2.460478196482179E-8*t**3*LOG(rh)*LOG(rhoa)**2 - & (0.05790872906645181*LOG(rh)*LOG(rhoa)**2)/x - & 0.1487119673397459*LOG(rhoa)**3 + & 0.002835082097822667*t*LOG(rhoa)**3 - & 9.24618825471694E-6*t**2*LOG(rhoa)**3 + & 5.004267665960894E-9*t**3*LOG(rhoa)**3 - & (0.01270805101481648*LOG(rhoa)**3)/x jnuc=EXP(jnuc) !1/(cm3s) ntot =-0.002954125078716302 - 0.0976834264241286*t + 0.001024847927067835*t**2 - 2.186459697726116E-6*t**3 - & 0.1017165718716887/x - 0.002050640345231486*LOG(rh) - 0.007585041382707174*t*LOG(rh) + & 0.0001926539658089536*t**2*LOG(rh) - 6.70429719683894E-7*t**3*LOG(rh) - & (0.2557744774673163*LOG(rh))/x + 0.003223076552477191*LOG(rh)**2 + 0.000852636632240633*t*LOG(rh)**2 - & 0.00001547571354871789*t**2*LOG(rh)**2 + 5.666608424980593E-8*t**3*LOG(rh)**2 + & (0.03384437400744206*LOG(rh)**2)/x + 0.04743226764572505*LOG(rh)**3 - & 0.0006251042204583412*t*LOG(rh)**3 + 2.650663328519478E-6*t**2*LOG(rh)**3 - & 3.674710848763778E-9*t**3*LOG(rh)**3 - (0.0002672510825259393*LOG(rh)**3)/x - & 0.01252108546759328*LOG(rhoa) + 0.005806550506277202*t*LOG(rhoa) - & 0.0001016735312443444*t**2*LOG(rhoa) + 2.881946187214505E-7*t**3*LOG(rhoa) + & (0.0942243379396279*LOG(rhoa))/x - 0.0385459592773097*LOG(rh)*LOG(rhoa) - & 0.0006723156277391984*t*LOG(rh)*LOG(rhoa) + 2.602884877659698E-6*t**2*LOG(rh)*LOG(rhoa) + & 1.194163699688297E-8*t**3*LOG(rh)*LOG(rhoa) - (0.00851515345806281*LOG(rh)*LOG(rhoa))/x - & 0.01837488495738111*LOG(rh)**2*LOG(rhoa) + 0.0001720723574407498*t*LOG(rh)**2*LOG(rhoa) - & 3.717657974086814E-7*t**2*LOG(rh)**2*LOG(rhoa) - & 5.148746022615196E-10*t**3*LOG(rh)**2*LOG(rhoa) + & (0.0002686602132926594*LOG(rh)**2*LOG(rhoa))/x - 0.06199739728812199*LOG(rhoa)**2 + & 0.000906958053583576*t*LOG(rhoa)**2 - 9.11727926129757E-7*t**2*LOG(rhoa)**2 - & 5.367963396508457E-9*t**3*LOG(rhoa)**2 - (0.007742343393937707*LOG(rhoa)**2)/x + & 0.0121827103101659*LOG(rh)*LOG(rhoa)**2 - 0.0001066499571188091*t*LOG(rh)*LOG(rhoa)**2 + & 2.534598655067518E-7*t**2*LOG(rh)*LOG(rhoa)**2 - & 3.635186504599571E-10*t**3*LOG(rh)*LOG(rhoa)**2 + & (0.0006100650851863252*LOG(rh)*LOG(rhoa)**2)/x + 0.0003201836700403512*LOG(rhoa)**3 - & 0.0000174761713262546*t*LOG(rhoa)**3 + 6.065037668052182E-8*t**2*LOG(rhoa)**3 - & 1.421771723004557E-11*t**3*LOG(rhoa)**3 + (0.0001357509859501723*LOG(rhoa)**3)/x ntot=EXP(ntot) rc=EXP(-1.6524245+0.42316402*x+0.33466487*LOG(ntot)) !nm IF (jnuc < 1.E-7) THEN jnuc=0.0 ENDIF IF (jnuc > 1.e10) THEN jnuc=1.e10 ENDIF rhotres=EXP( -279.2430007512709 + 11.73439886096903*rh + 22700.92970508331/t & - (1088.644983466801*rh)/t + 1.144362942094912*t & - 0.03023314602163684*rh*t - 0.001302541390154324*t**2 & - 6.386965238433532*LOG(rh) + (854.980361026715*LOG(rh))/t & + 0.00879662256826497*t*LOG(rh)) !1/cm3 END SUBROUTINE binapara !--------------------------------------------------------------------------------------------------- SUBROUTINE newbinapara(t,satrat,rhoa,csi,airn,ipr,jnuc_n_real,ntot_n_real,jnuc_i_real,ntot_i_real, & x_n_real,x_i_real,na_n_real,na_i_real,rc_n_real,rc_i_real,n_i_real, & kinetic_n,kinetic_i) ! Fortran 90 SUBROUTINE newbinapara ! Calculates parametrized values for neutral and ion-induced sulfuric acid-water particle formation rate ! of critical clusters, ! number of particle in the critical clusters, the radii of the critical clusters ! in H2O-H2SO4-ion system if temperature, saturation ratio of water, sulfuric acid concentration, ! and, optionally, either condensation sink due to pre-existing particle and ion pair production rate, ! or atmospheric concentration of negative ions are given. ! The code calculates also the kinetic limit and the particle formation rate ! above this limit (in which case we set ntot=1 and na=1) ! Copyright (C)2018 Määttänen et al. 2018 ! anni.maattanen@latmos.ipsl.fr ! joonas.merikanto@fmi.fi ! hanna.vehkamaki@helsinki.fi ! References ! A. Määttänen, J. Merikanto, H. Henschel, J. Duplissy, R. Makkonen, ! I. K. Ortega and H. Vehkamäki (2018), New parameterizations for ! neutral and ion-induced sulfuric acid-water particle formation in ! nucleation and kinetic regimes, J. Geophys. Res. Atmos., 122, doi:10.1002/2017JD027429. ! Brasseur, G., and A. Chatel (1983), paper presented at the 9th Annual Meeting of the ! European Geophysical Society, Leeds, Great Britain, August 1982. ! Dunne, Eimear M., et al.(2016), Global atmospheric particle formation from CERN CLOUD measurements, ! Science 354.6316, 1119-1124. USE aerophys USE lmdz_yomcst IMPLICIT NONE !---------------------------------------------------- !Global intent in REAL,INTENT(IN) :: t ! temperature in K REAL,INTENT(IN) :: satrat ! saturatio ratio of water (between zero and 1) REAL,INTENT(IN) :: rhoa ! sulfuric acid concentration in 1/cm3 REAL,INTENT(IN) :: csi ! Ion condensation sink (s-1) REAL,INTENT(IN) :: airn ! Air molecule concentration in (cm-3) REAL,INTENT(IN) :: ipr ! Ion pair production rate (cm-3 s-1) !Global intent out REAL,INTENT(OUT) :: jnuc_n_real ! Neutral nucleation rate in 1/cm3s (J>10^-7 1/cm3s) REAL,INTENT(OUT) :: ntot_n_real ! total number of molecules in the neutral critical cluster REAL,INTENT(OUT) :: jnuc_i_real ! Charged nucleation rate in 1/cm3s (J>10^-7 1/cm3s) REAL,INTENT(OUT) :: ntot_i_real ! total number of molecules in the charged critical cluster REAL,INTENT(OUT) :: x_n_real ! mole fraction of H2SO4 in the neutral critical cluster REAL,INTENT(OUT) :: x_i_real ! mole fraction of H2SO4 in the charged critical cluster ! (note that x_n=x_i in nucleation regime) REAL,INTENT(OUT) :: na_n_real ! sulfuric acid molecules in the neutral critical cluster REAL,INTENT(OUT) :: na_i_real ! sulfuric molecules in the charged critical cluster REAL,INTENT(OUT) :: rc_n_real ! radius of the charged critical cluster in nm REAL,INTENT(OUT) :: rc_i_real ! radius of the charged critical cluster in nm REAL,INTENT(OUT) :: n_i_real ! number of ion pairs in air (cm-3) LOGICAL,INTENT(OUT) :: kinetic_n ! true if kinetic neutral nucleation LOGICAL,INTENT(OUT) :: kinetic_i ! true if kinetic ion-induced nucleation ! Local DOUBLE PRECISION :: jnuc_n ! Neutral nucleation rate in 1/cm3s (J>10^-7 1/cm3s) DOUBLE PRECISION :: ntot_n ! total number of molecules in the neutral critical cluster DOUBLE PRECISION :: jnuc_i ! Charged nucleation rate in 1/cm3s (J>10^-7 1/cm3s) DOUBLE PRECISION :: ntot_i ! total number of molecules in the charged critical cluster DOUBLE PRECISION :: x_n ! mole fraction of H2SO4 in the neutral critical cluster DOUBLE PRECISION :: x_i ! mole fraction of H2SO4 in the charged critical cluster ! (note that x_n=x_i in nucleation regime) DOUBLE PRECISION :: na_n ! sulfuric acid molecules in the neutral critical cluster DOUBLE PRECISION :: na_i ! sulfuric molecules in the charged critical cluster DOUBLE PRECISION :: rc_n ! radius of the charged critical cluster in nm DOUBLE PRECISION :: rc_i ! radius of the charged critical cluster in nm DOUBLE PRECISION :: n_i ! number of ion pairs in air (cm-3) DOUBLE PRECISION :: x ! mole fraction of H2SO4 in the critical cluster DOUBLE PRECISION :: satratln ! bounded water saturation ratio for neutral case (between 5.E-6 - 1.0) DOUBLE PRECISION :: satratli ! bounded water saturation ratio for ion-induced case (between 1.E-7 - 0.95) DOUBLE PRECISION :: rhoaln ! bounded concentration of h2so4 for neutral case (between 10^10 - 10^19 m-3) DOUBLE PRECISION :: rhoali ! bounded concentration of h2so4 for ion-induced case (between 10^10 - 10^22 m-3) DOUBLE PRECISION :: tln ! bounded temperature for neutral case (between 165-400 K) DOUBLE PRECISION :: tli ! bounded temperature for ion-induced case (195-400 K) DOUBLE PRECISION :: kinrhotresn ! threshold sulfuric acid for neutral kinetic nucleation DOUBLE PRECISION :: kinrhotresi ! threshold sulfuric acid for ion-induced kinetic nucleation DOUBLE PRECISION :: jnuc_i1 ! Ion-induced rate for n_i=1 cm-3 DOUBLE PRECISION :: xloss ! Ion loss rate DOUBLE PRECISION :: recomb ! Ion-ion recombination rate !--- 0) Initializations: kinetic_n=.FALSE. kinetic_i=.FALSE. jnuc_n=0.0 jnuc_i=0.0 ntot_n=0.0 ntot_i=0.0 na_n=0.0 na_i=0.0 rc_n=0.0 rc_i=0.0 x=0.0 x_n=0.0 x_i=0.0 satratln=satrat satratli=satrat rhoaln=rhoa rhoali=rhoa tln=t tli=t n_i=0.0 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !Boundary values according to parameterization limits !Temperature bounds IF (t<=165.) THEN tln=165.0 ENDIF IF (t<=195.) THEN tli=195.0 ENDIF IF (t>=400.) THEN tln=400. tli=400. ENDIF ! Saturation ratio bounds IF (satrat<1.E-7) THEN satratli=1.E-7 ENDIF IF (satrat<1.E-5) THEN satratln=1.E-5 ENDIF IF (satrat>0.95) THEN satratli=0.95 ENDIF IF (satrat>1.0) THEN satratln=1.0 ENDIF ! Sulfuric acid concentration bounds IF (rhoa<=1.E4) THEN rhoaln=1.E4 rhoali=1.E4 ENDIF IF (rhoa>1.E13) THEN rhoaln=1.E13 ENDIF IF (rhoa>1.E16) THEN rhoali=1.E16 ENDIF !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !Critical cluster composition (valid for both cases, bounds not used here) x_n= 7.9036365428891719E-1 - 2.8414059650092153E-3*tln + 1.4976802556584141E-2*LOG(satratln) & - 2.4511581740839115E-4*tln*LOG(satratln) + 3.4319869471066424E-3 *LOG(satratln)**2 & - 2.8799393617748428E-5*tln*LOG(satratln)**2 + 3.0174314126331765E-4*LOG(satratln)**3 & - 2.2673492408841294E-6*tln*LOG(satratln)**3 - 4.3948464567032377E-3*LOG(rhoaln) & + 5.3305314722492146E-5*tln*LOG(rhoaln) x_i= 7.9036365428891719E-1 - 2.8414059650092153E-3*tli + 1.4976802556584141E-2*LOG(satratli) & - 2.4511581740839115E-4*tli*LOG(satratli) + 3.4319869471066424E-3 *LOG(satratli)**2 & - 2.8799393617748428E-5*tli*LOG(satratli)**2 + 3.0174314126331765E-4*LOG(satratli)**3 & - 2.2673492408841294E-6*tli*LOG(satratli)**3 - 4.3948464567032377E-3*LOG(rhoali) & + 5.3305314722492146E-5*tli*LOG(rhoali) x_n=MIN(MAX(x_n,1.E-30),1.) x_i=MIN(MAX(x_i,1.E-30),1.) !Neutral nucleation !Kinetic limit check IF (satratln >= 1.E-2 .AND. satratln <= 1.) THEN kinrhotresn=EXP(7.8920778706888086E+1 + 7.3665492897447082*satratln - 1.2420166571163805E+4/tln & + (-6.1831234251470971E+2*satratln)/tln - 2.4501159970109945E-2*tln & -1.3463066443605762E-2*satratln*tln + 8.3736373989909194E-06*tln**2 & -1.4673887785408892*LOG(satratln) + (-3.2141890006517094E+1*LOG(satratln))/tln & + 2.7137429081917556E-3*tln*LOG(satratln)) !1/cm3 IF (kinrhotresn= 1.E-4 .AND. satratln < 1.E-2) THEN kinrhotresn=EXP(7.9074383049843647E+1 - 2.8746005462158347E+1*satratln - 1.2070272068458380E+4/tln & + (-5.9205040320056632E+3*satratln)/tln - 2.4800372593452726E-2*tln & -4.3983007681295948E-2*satratln*tln + 2.5943854791342071E-5*tln**2 & -2.3141363245211317*LOG(satratln) + (9.9186787997857735E+1*LOG(satratln))/tln & + 5.6819382556144681E-3*tln*LOG(satratln)) !1/cm3 IF (kinrhotresn= 5.E-6 .AND. satratln < 1.E-4) THEN kinrhotresn=EXP(8.5599712000361677E+1 + 2.7335119660796581E+3*satratln - 1.1842350246291651E+4/tln & + (-1.2439843468881438E+6*satratln)/tln - 5.4536964974944230E-2*tln & + 5.0886987425326087*satratln*tln + 7.1964722655507067E-5*tln**2 & -2.4472627526306372*LOG(satratln) + (1.7561478001423779E+2*LOG(satratln))/tln & + 6.2640132818141811E-3*tln*LOG(satratln)) !1/cm3 IF (kinrhotresn0.0) THEN ! if the ion production rate is above zero ! Calculate the ion induced nucleation rate wrt. concentration of 1 ion/cm3 kinrhotresi = 5.3742280876674478E1 - 6.6837931590012266E-3 *LOG(satratli)**(-2) & - 1.0142598385422842E-01 * LOG(satratli)**(-1) - 6.4170597272606873E+00 * LOG(satratli) & - 6.4315798914824518E-01 * LOG(satratli)**2 - 2.4428391714772721E-02 * LOG(satratli)**3 & - 3.5356658734539019E-04 * LOG(satratli)**4 + 2.5400015099140506E-05 * tli * LOG(satratli)**(-2) & - 2.7928900816637790E-04 * tli * LOG(satratli)**(-1) + 4.4108573484923690E-02 * tli * LOG(satratli) & + 6.3943789012475532E-03 * tli * LOG(satratli)**(2) + 2.3164296174966580E-04 * tli * LOG(satratli)**(3) & + 3.0372070669934950E-06 * tli * LOG(satratli)**4 + 3.8255873977423475E-06 * tli**2 * LOG(satratli)**(-1) & - 1.2344793083561629E-04 * tli**2 * LOG(satratli) - 1.7959048869810192E-05 * tli**2 * LOG(satratli)**(2) & - 3.2165622558722767E-07 * tli**2 * LOG(satratli)**3 - 4.7136923780988659E-09 * tli**3 * LOG(satratli)**(-1) & + 1.1873317184482216E-07 * tli**3 * LOG(satratli) + 1.5685860354866621E-08 * tli**3 * LOG(satratli)**2 & - 1.4329645891059557E+04 * tli**(-1) + 1.3842599842575321E-01 * tli & - 4.1376265912842938E-04 * tli**(2) + 3.9147639775826004E-07 * tli**3 kinrhotresi=EXP(kinrhotresi) !1/cm3 IF (kinrhotresi