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

Last change on this file since 1944 was 1268, checked in by aslmd, 11 years ago

LMDZ.MARS. related to r1266. forgot to remove a few now-obsolete dimensions.h includes in Mars physics.

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