source: trunk/LMDZ.MARS/libf/phymars/nuclea.F @ 3807

Last change on this file since 3807 was 3740, checked in by emillour, 7 weeks ago

Mars PCM:
Code tidying; removed unused mufract.F (mucorr.F does the job); turned
ambiguously named sig.F to sig_h2o.F90 and make it a module.
EM

File size: 6.9 KB
Line 
1      MODULE nuclea_mod
2     
3      IMPLICIT NONE
4     
5      CONTAINS
6
7      subroutine nuclea(ph2o,temp,sat,n_ccn,nucrate)
8      use comcstfi_h, only: pi
9      use microphys_h, only: nbin_cld, rad_cld, nav, mteta, m0
10      use microphys_h, only: desorp, kbz, nus, rgp, surfdif, vo1
11      use callkeys_mod, only: temp_dependent_m, cloud_adapt_ts
12      use sig_h2o_mod, only: sig_h2o
13      implicit none
14*                                                     *
15*   This subroutine computes the nucleation rate      *
16*   as given in Pruppacher & Klett (1978) in the      *
17*   case of water ice forming on a solid substrate.   *
18*     Definition refined by Keese (jgr,1989)          *
19*   Authors: F. Montmessin                            *
20*     Adapted for the LMD/GCM by J.-B. Madeleine      *
21*     (October 2011)                                  *
22*     Optimisation by A. Spiga (February 2012)        * 
23*******************************************************
24
25c     Inputs
26      DOUBLE PRECISION, INTENT(IN) :: ph2o,sat
27      DOUBLE PRECISION, INTENT(IN) :: n_ccn(nbin_cld)
28      REAL, INTENT(IN) :: temp
29
30c     Output
31   !   DOUBLE PRECISION nucrate(nbin_cld)
32      REAL, INTENT(OUT) :: nucrate(nbin_cld)
33
34c     Local variables
35      DOUBLE PRECISION nh2o
36      DOUBLE PRECISION rstar    ! Radius of the critical germ (m)
37      DOUBLE PRECISION gstar    ! # of molecules forming a critical embryo
38      DOUBLE PRECISION fistar   ! Activation energy required to form a critical embryo (J)
39!      DOUBLE PRECISION zeldov   ! Zeldovitch factor (no dim)
40      DOUBLE PRECISION deltaf
41
42c     Ratio rstar/radius of the nucleating dust particle
43c     double precision xratio
44     
45      double precision mtetalocal ! local mteta in double precision
46
47      double precision fshapesimple,zefshape
48
49
50      integer i
51     
52      LOGICAL, SAVE :: firstcall = .true.
53!$OMP THREADPRIVATE(firstcall)
54
55c     *************************************************
56
57      mtetalocal = mteta  !! use mtetalocal for better performance
58
59      IF (temp_dependent_m) THEN
60c     J.Naar - sep 2023 :
61        if (.not.cloud_adapt_ts) then
62          ! Simple linear parametrisation from Maattaanen 2014
63          ! Maxed out at 0.97 for physical realism
64          ! Used to tune the WC without adaptative ts of microphy (MCD6.1 configuration)
65          mtetalocal = min(0.0044*temp + 0.1831,0.97)
66        else
67          ! With adapt_ts, need to use this relation (same paper, tanh relation):
68          mtetalocal = 0.469+((0.972-0.469)*tanh((temp/158.282)**4.244))
69        endif ! (.not.cloud_adapt_ts)
70      ENDIF ! (temp_dependent_m)
71cccccccccccccccccccccccccccccccccccccccccccccccccc
72ccccccccccc ESSAIS TN MTETA = F (T) cccccccccccccc
73c      if (temp .gt. 200) then
74c         mtetalocal = mtetalocal
75c      else if (temp .lt. 190) then
76c         mtetalocal = mtetalocal-0.05
77c      else
78c         mtetalocal = mtetalocal - (190-temp)*0.005
79c      endif
80c----------------exp law, see Trainer 2008, J. Phys. Chem. C 2009, 113, 2036\u20132040
81       !mtetalocal = max(mtetalocal - 6005*exp(-0.065*temp),0.1)
82       !mtetalocal = max(mtetalocal - 6005*exp(-0.068*temp),0.1)
83               !print*, mtetalocal, temp
84cccccccccccccccccccccccccccccccccccccccccccccccccc
85cccccccccccccccccccccccccccccccccccccccccccccccccc
86      IF (firstcall.and.temp_dependent_m) THEN
87        if (.not.cloud_adapt_ts) then
88          print*, ' ' 
89          print*, 'dear user, please keep in mind that'
90          print*, 'contact parameter IS NOT constant ;'
91          print*, 'Using the following linear fit from'
92          print*, 'Maattanen et al. 2014 (SM linear fit) :'
93          print*, 'm=min(0.0044*temp + 0.1831,0.97)'
94          print*, ' '
95        else !cloud_adapt_ts=.true.
96          print*, ' ' 
97          print*, 'dear user, please keep in mind that'
98          print*, 'contact parameter IS NOT constant ;'
99          print*, 'Using the tanh fit n2 (jsc sample) from'
100          print*, 'Maattanen et al. 2014 (10.1016/j.grj.2014.09.002) :'
101          print*, 'm=0.469+((0.972-0.469)*tanh((temp/158.282)**4.244))'
102          print*, ' '
103        endif
104        firstcall=.false.
105      ELSE IF (firstcall.and.(.not.(temp_dependent_m))) THEN
106        print*, ' ' 
107        print*, 'dear user, please keep in mind that'
108        print*, 'contact parameter IS constant'
109        print*, ' ' 
110        firstcall=.false.
111      END IF
112cccccccccccccccccccccccccccccccccccccccccccccccccc
113cccccccccccccccccccccccccccccccccccccccccccccccccc
114   
115
116      if (sat .gt. 1.) then    ! minimum condition to activate nucleation
117
118        nh2o   = ph2o / kbz / temp
119        rstar  = 2. * sig_h2o(temp) * vo1 / (rgp*temp*log(sat))
120        gstar  = 4. * nav * pi * (rstar * rstar * rstar) / (3.*vo1)
121       
122        fshapesimple = (2.+mtetalocal)*(1.-mtetalocal)*(1.-mtetalocal)
123     &                   / 4.
124
125c       Loop over size bins
126        do i=1,nbin_cld
127
128          if ( n_ccn(i) .lt. 1e-10 ) then
129c           no dust, no need to compute nucleation!
130            nucrate(i)=0.
131            ! move on to next bin
132            cycle
133          endif
134
135          if (rad_cld(i).gt.3000.*rstar) then
136            zefshape = fshapesimple
137          else
138            zefshape = fshape(mtetalocal,rad_cld(i)/rstar)
139          endif
140
141          fistar = (4./3.*pi) * sig_h2o(temp) * (rstar * rstar) *
142     &             zefshape
143          deltaf = (2.*desorp-surfdif-fistar)/
144     &             (kbz*temp)
145          deltaf = min( max(deltaf, -100.d0), 100.d0)
146
147          if (deltaf.eq.-100.) then
148            nucrate(i) = 0.
149          else
150            nucrate(i)= real(sqrt ( fistar /
151     &               (3.*pi*kbz*temp*(gstar*gstar)) )
152     &                  * kbz * temp * rstar
153     &                  * rstar * 4. * pi
154     &                  * ( nh2o*rad_cld(i) )
155     &                  * ( nh2o*rad_cld(i) )
156     &                  / ( zefshape * nus * m0 )
157     &                  * exp (deltaf))
158          endif
159
160        enddo ! of do i=1,nbin_cld
161
162      else
163
164        do i=1,nbin_cld
165          nucrate(i) = 0.
166        enddo
167
168      endif ! of if (sat .gt. 1.)
169
170      end subroutine nuclea
171
172*********************************************************
173      double precision function fshape(cost,rap)
174      implicit none
175*        function computing the f(m,x) factor           *
176* related to energy required to form a critical embryo  *
177*********************************************************
178
179      double precision, intent(in) :: cost,rap
180      double precision yeah
181
182          !! PHI
183          yeah = sqrt( 1. - 2.*cost*rap + rap*rap )
184          !! FSHAPE = TERM A
185          fshape = (1.-cost*rap) / yeah
186          fshape = fshape * fshape * fshape
187          fshape = 1. + fshape
188          !! ... + TERM B
189          yeah = (rap-cost)/yeah
190          fshape = fshape +
191     & rap*rap*rap*(2.-3.*yeah+yeah*yeah*yeah)
192          !! ... + TERM C
193          fshape = fshape + 3. * cost * rap * rap * (yeah-1.)
194          !! FACTOR 1/2
195          fshape = 0.5*fshape
196
197      end function fshape
198
199
200      END MODULE nuclea_mod
Note: See TracBrowser for help on using the repository browser.