! *************************** ternary_fit.f90 ******************************** ! Joonas Merikanto, 2006 ! ! Fortran 90 subroutine that calculates the parameterized composition ! and nucleation rate of critical clusters in h2o-h2so4-nh3 vapor ! ! WARNING: The fit should not be used outside its limits of validity ! (limits indicated below) ! ! IN: ! T: temperature (K), limits 235-295 K ! rh: relative humidity as fraction (eg. 0.5=50%) limits 0.05-0.95 ! c2: sulfuric acid concentration (molecules/cm3) limits 5x104 - 109 molecules/cm3 ! c3: ammonia mixing ratio (ppt) limits 0.1 - 1000 ppt ! ! OUT: ! J_log: logarithm of nucleation rate (1/(s cm3)) ! ntot: total number of molecules in the critical cluster ! nacid: number of sulfuric acid molecules in the critical cluster ! namm: number of ammonia molecules in the critical cluster ! r: radius of the critical cluster (nm) ! **************************************************************************** SUBROUTINE ternary_fit(t,rh,c2,c3,J_log,ntot,nacid,namm,r) IMPLICIT NONE real,intent(in) :: t,rh,c2,c3 real,intent(out) :: J_log,ntot,nacid,namm, r real :: J,t_onset t_onset=143.6002929064716 + 1.0178856665693992*rh + & & 10.196398812974294*Log(c2) - & & 0.1849879416839113*Log(c2)**2 - 17.161783213150173*Log(c3) + & & (109.92469248546053*Log(c3))/Log(c2) + & & 0.7734119613144357*Log(c2)*Log(c3) - 0.15576469879527022*Log(c3)**2 if(t_onset.gt.t) then J_log=-12.861848898625231 + 4.905527742256349*c3 - 358.2337705052991*rh -& & 0.05463019231872484*c3*t + 4.8630382337426985*rh*t + & & 0.00020258394697064567*c3*t**2 - 0.02175548069741675*rh*t**2 - & & 2.502406532869512e-7*c3*t**3 + 0.00003212869941055865*rh*t**3 - & & 4.39129415725234e6/Log(c2)**2 + (56383.93843154586*t)/Log(c2)**2 -& & (239.835990963361*t**2)/Log(c2)**2 + & & (0.33765136625580167*t**3)/Log(c2)**2 - & & (629.7882041830943*rh)/(c3**3*Log(c2)) + & & (7.772806552631709*rh*t)/(c3**3*Log(c2)) - & & (0.031974053936299256*rh*t**2)/(c3**3*Log(c2)) + & & (0.00004383764128775082*rh*t**3)/(c3**3*Log(c2)) + & & 1200.472096232311*Log(c2) - 17.37107890065621*t*Log(c2) + & & 0.08170681335921742*t**2*Log(c2) - 0.00012534476159729881*t**3*Log(c2) - & & 14.833042158178936*Log(c2)**2 + 0.2932631303555295*t*Log(c2)**2 - & & 0.0016497524241142845*t**2*Log(c2)**2 + & & 2.844074805239367e-6*t**3*Log(c2)**2 - 231375.56676032578*Log(c3) - & & 100.21645273730675*rh*Log(c3) + 2919.2852552424706*t*Log(c3) + & & 0.977886555834732*rh*t*Log(c3) - 12.286497122264588*t**2*Log(c3) - & & 0.0030511783284506377*rh*t**2*Log(c3) + & & 0.017249301826661612*t**3*Log(c3) + 2.967320346100855e-6*rh*t**3*Log(c3) + & & (2.360931724951942e6*Log(c3))/Log(c2) - & & (29752.130254319443*t*Log(c3))/Log(c2) + & & (125.04965118142027*t**2*Log(c3))/Log(c2) - & & (0.1752996881934318*t**3*Log(c3))/Log(c2) + & & 5599.912337254629*Log(c2)*Log(c3) - 70.70896612937771*t*Log(c2)*Log(c3) + & & 0.2978801613269466*t**2*Log(c2)*Log(c3) - & & 0.00041866525019504*t**3*Log(c2)*Log(c3) + 75061.15281456841*Log(c3)**2 - & & 931.8802278173565*t*Log(c3)**2 + 3.863266220840964*t**2*Log(c3)**2 - & & 0.005349472062284983*t**3*Log(c3)**2 - & & (732006.8180571689*Log(c3)**2)/Log(c2) + & & (9100.06398573816*t*Log(c3)**2)/Log(c2) - & & (37.771091915932004*t**2*Log(c3)**2)/Log(c2) + & & (0.05235455395566905*t**3*Log(c3)**2)/Log(c2) - & & 1911.0303773001353*Log(c2)*Log(c3)**2 + & & 23.6903969622286*t*Log(c2)*Log(c3)**2 - & & 0.09807872005428583*t**2*Log(c2)*Log(c3)**2 + & & 0.00013564560238552576*t**3*Log(c2)*Log(c3)**2 - & & 3180.5610833308*Log(c3)**3 + 39.08268568672095*t*Log(c3)**3 - & & 0.16048521066690752*t**2*Log(c3)**3 + & & 0.00022031380023793877*t**3*Log(c3)**3 + & & (40751.075322248245*Log(c3)**3)/Log(c2) - & & (501.66977622013934*t*Log(c3)**3)/Log(c2) + & & (2.063469732254135*t**2*Log(c3)**3)/Log(c2) - & & (0.002836873785758324*t**3*Log(c3)**3)/Log(c2) + & & 2.792313345723013*Log(c2)**2*Log(c3)**3 - & & 0.03422552111802899*t*Log(c2)**2*Log(c3)**3 + & & 0.00014019195277521142*t**2*Log(c2)**2*Log(c3)**3 - & & 1.9201227328396297e-7*t**3*Log(c2)**2*Log(c3)**3 - & & 980.923146020468*Log(rh) + 10.054155220444462*t*Log(rh) - & & 0.03306644502023841*t**2*Log(rh) + 0.000034274041225891804*t**3*Log(rh) + & & (16597.75554295064*Log(rh))/Log(c2) - & & (175.2365504237746*t*Log(rh))/Log(c2) + & & (0.6033215603167458*t**2*Log(rh))/Log(c2) - & & (0.0006731787599587544*t**3*Log(rh))/Log(c2) - & & 89.38961120336789*Log(c3)*Log(rh) + 1.153344219304926*t*Log(c3)*Log(rh) - & & 0.004954549700267233*t**2*Log(c3)*Log(rh) + & & 7.096309866238719e-6*t**3*Log(c3)*Log(rh) + & & 3.1712136610383244*Log(c3)**3*Log(rh) - & & 0.037822330602328806*t*Log(c3)**3*Log(rh) + & & 0.0001500555743561457*t**2*Log(c3)**3*Log(rh) - & & 1.9828365865570703e-7*t**3*Log(c3)**3*Log(rh) J=exp(J_log) ntot=57.40091052369212 - 0.2996341884645408*t + & & 0.0007395477768531926*t**2 - & & 5.090604835032423*Log(c2) + 0.011016634044531128*t*Log(c2) + & & 0.06750032251225707*Log(c2)**2 - 0.8102831333223962*Log(c3) + & & 0.015905081275952426*t*Log(c3) - 0.2044174683159531*Log(c2)*Log(c3) + & & 0.08918159167625832*Log(c3)**2 - 0.0004969033586666147*t*Log(c3)**2 + & & 0.005704394549007816*Log(c3)**3 + 3.4098703903474368*Log(J) - & & 0.014916956508210809*t*Log(J) + 0.08459090011666293*Log(c3)*Log(J) - & & 0.00014800625143907616*t*Log(c3)*Log(J) + 0.00503804694656905*Log(J)**2 r=3.2888553966535506e-10 - 3.374171768439839e-12*t + & & 1.8347359507774313e-14*t**2 + 2.5419844298881856e-12*Log(c2) - & & 9.498107643050827e-14*t*Log(c2) + 7.446266520834559e-13*Log(c2)**2 + & & 2.4303397746137294e-11*Log(c3) + 1.589324325956633e-14*t*Log(c3) - & & 2.034596219775266e-12*Log(c2)*Log(c3) - 5.59303954457172e-13*Log(c3)**2 - & & 4.889507104645867e-16*t*Log(c3)**2 + 1.3847024107506764e-13*Log(c3)**3 + & & 4.141077193427042e-15*Log(J) - 2.6813110884009767e-14*t*Log(J) + & & 1.2879071621313094e-12*Log(c3)*Log(J) - & & 3.80352446061867e-15*t*Log(c3)*Log(J) - 1.8790172502456827e-14*Log(J)**2 nacid=-4.7154180661803595 + 0.13436423483953885*t - & & 0.00047184686478816176*t**2 - & & 2.564010713640308*Log(c2) + 0.011353312899114723*t*Log(c2) + & & 0.0010801941974317014*Log(c2)**2 + 0.5171368624197119*Log(c3) - & & 0.0027882479896204665*t*Log(c3) + 0.8066971907026886*Log(c3)**2 - & & 0.0031849094214409335*t*Log(c3)**2 - 0.09951184152927882*Log(c3)**3 + & & 0.00040072788891745513*t*Log(c3)**3 + 1.3276469271073974*Log(J) - & & 0.006167654171986281*t*Log(J) - 0.11061390967822708*Log(c3)*Log(J) + & & 0.0004367575329273496*t*Log(c3)*Log(J) + 0.000916366357266258*Log(J)**2 namm=71.20073903979772 - 0.8409600103431923*t + & & 0.0024803006590334922*t**2 + & & 2.7798606841602607*Log(c2) - 0.01475023348171676*t*Log(c2) + & & 0.012264508212031405*Log(c2)**2 - 2.009926050440182*Log(c3) + & & 0.008689123511431527*t*Log(c3) - 0.009141180198955415*Log(c2)*Log(c3) + & & 0.1374122553905617*Log(c3)**2 - 0.0006253227821679215*t*Log(c3)**2 + & & 0.00009377332742098946*Log(c3)**3 + 0.5202974341687757*Log(J) - & & 0.002419872323052805*t*Log(J) + 0.07916392322884074*Log(c3)*Log(J) - & & 0.0003021586030317366*t*Log(c3)*Log(J) + 0.0046977006608603395*Log(J)**2 else ! Nucleation rate less that 5E-6, setting j_log arbitrary small j_log=-300. end if Return END ternary_fit.f90 Content-Type: text/x-fortran Content-Encoding: base64 JMerikanto_thesis_intro.pdf Content-Type: application/pdf Content-Encoding: base64