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

Last change on this file since 1009 was 706, checked in by emillour, 12 years ago

Mars GCM:

  • Minor fix in "nuclea.F", max() and min() functions must have arguments of identical types.
  • Bug correction in "physiq.F": only water (and possibly dust and cnn if using microphysics) tracer tendencies should be updated after call to watercloud.

EM

File size: 5.5 KB
Line 
1*******************************************************
2*                                                     *
3      subroutine nuclea(ph2o,temp,sat,n_ccn,nucrate)
4      implicit none
5*                                                     *
6*   This subroutine computes the nucleation rate      *
7*   as given in Pruppacher & Klett (1978) in the      *
8*   case of water ice forming on a solid substrate.   *
9*     Definition refined by Keese (jgr,1989)          *
10*   Authors: F. Montmessin                            *
11*     Adapted for the LMD/GCM by J.-B. Madeleine      *
12*     (October 2011)                                  *
13*     Optimisation by A. Spiga (February 2012)        * 
14*******************************************************
15
16#include "dimensions.h"
17#include "dimphys.h"
18#include "comcstfi.h"
19#include "tracer.h"
20#include "microphys.h"
21
22c     Inputs
23      DOUBLE PRECISION ph2o,sat
24      DOUBLE PRECISION n_ccn(nbin_cld)
25      REAL temp
26
27c     Output
28   !   DOUBLE PRECISION nucrate(nbin_cld)
29      REAL nucrate(nbin_cld)
30
31c     Local variables
32      DOUBLE PRECISION nh2o
33      DOUBLE PRECISION sig      ! Water-ice/air surface tension  (N.m)
34      external sig
35      DOUBLE PRECISION rstar    ! Radius of the critical germ (m)
36      DOUBLE PRECISION gstar    ! # of molecules forming a critical embryo
37      DOUBLE PRECISION fistar   ! Activation energy required to form a critical embryo (J)
38!      DOUBLE PRECISION zeldov   ! Zeldovitch factor (no dim)
39      DOUBLE PRECISION fshape   ! function defined at the end of the file
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 firstcall
53      DATA firstcall/.true./
54      SAVE firstcall
55
56c     *************************************************
57
58      mtetalocal = mteta  !! use mtetalocal for better performance
59
60cccccccccccccccccccccccccccccccccccccccccccccccccc
61ccccccccccc ESSAIS TN MTETA = F (T) cccccccccccccc
62c      if (temp .gt. 200) then
63c         mtetalocal = mtetalocal
64c      else if (temp .lt. 190) then
65c         mtetalocal = mtetalocal-0.05
66c      else
67c         mtetalocal = mtetalocal - (190-temp)*0.005
68c      endif
69c----------------exp law, see Trainer 2008, J. Phys. Chem. C 2009, 113, 2036\u20132040
70       !mtetalocal = max(mtetalocal - 6005*exp(-0.065*temp),0.1)
71       !mtetalocal = max(mtetalocal - 6005*exp(-0.068*temp),0.1)
72               !print*, mtetalocal, temp
73cccccccccccccccccccccccccccccccccccccccccccccccccc
74cccccccccccccccccccccccccccccccccccccccccccccccccc
75      IF (firstcall) THEN
76          print*, ' ' 
77          print*, 'dear user, please keep in mind that'
78          print*, 'contact parameter IS constant'
79          !print*, 'contact parameter IS NOT constant:'
80          !print*, 'max(mteta - 6005*exp(-0.065*temp),0.1)'
81          !print*, 'max(mteta - 6005*exp(-0.068*temp),0.1)'
82          print*, ' ' 
83         firstcall=.false.
84      END IF
85cccccccccccccccccccccccccccccccccccccccccccccccccc
86cccccccccccccccccccccccccccccccccccccccccccccccccc
87   
88
89      if (sat .gt. 1.) then    ! minimum condition to activate nucleation
90
91        nh2o   = ph2o / kbz / temp
92        rstar  = 2. * sig(temp) * vo1 / (rgp*temp*dlog(sat))
93        gstar  = 4. * nav * pi * (rstar * rstar * rstar) / (3.*vo1)
94       
95        fshapesimple = (2.+mtetalocal)*(1.-mtetalocal)*(1.-mtetalocal)
96     &                   / 4.
97
98c       Loop over size bins
99        do 200 i=1,nbin_cld
100
101          if ( n_ccn(i) .lt. 1e-10 ) then
102c           no dust, no need to compute nucleation!
103            nucrate(i)=0.
104            goto 200
105          endif
106
107          if (rad_cld(i).gt.3000.*rstar) then
108            zefshape = fshapesimple
109          else
110            zefshape = fshape(mtetalocal,rad_cld(i)/rstar)
111          endif
112
113          fistar = (4./3.*pi) * sig(temp) * (rstar * rstar) *
114     &             zefshape
115          deltaf = (2.*desorp-surfdif-fistar)/
116     &             (kbz*temp)
117          deltaf = min( max(deltaf, -100.d0), 100.d0)
118
119          if (deltaf.eq.-100.) then
120            nucrate(i) = 0.
121          else
122            nucrate(i)= real(sqrt ( fistar /
123     &               (3.*pi*kbz*temp*(gstar*gstar)) )
124     &                  * kbz * temp * rstar
125     &                  * rstar * 4. * pi
126     &                  * ( nh2o*rad_cld(i) )
127     &                  * ( nh2o*rad_cld(i) )
128     &                  / ( zefshape * nus * m0 )
129     &                  * dexp (deltaf))
130          endif
131
132200     continue
133
134      else
135
136        do i=1,nbin_cld
137          nucrate(i) = 0.
138        enddo
139
140      endif
141
142      return
143      end
144
145*********************************************************
146      double precision function fshape(cost,rap)
147      implicit none
148*        function computing the f(m,x) factor           *
149* related to energy required to form a critical embryo  *
150*********************************************************
151
152      double precision cost,rap
153      double precision yeah
154
155          !! PHI
156          yeah = sqrt( 1. - 2.*cost*rap + rap*rap )
157          !! FSHAPE = TERM A
158          fshape = (1.-cost*rap) / yeah
159          fshape = fshape * fshape * fshape
160          fshape = 1. + fshape
161          !! ... + TERM B
162          yeah = (rap-cost)/yeah
163          fshape = fshape +
164     & rap*rap*rap*(2.-3.*yeah+yeah*yeah*yeah)
165          !! ... + TERM C
166          fshape = fshape + 3. * cost * rap * rap * (yeah-1.)
167          !! FACTOR 1/2
168          fshape = 0.5*fshape
169
170      return
171      end
Note: See TracBrowser for help on using the repository browser.