source: LMDZ4/trunk/libf/phylmd/clouds_gno.F @ 524

Last change on this file since 524 was 524, checked in by lmdzadmin, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 8.0 KB
Line 
1!
2! $Header$
3!
4C
5C================================================================================
6C
7      SUBROUTINE CLOUDS_GNO(klon,ND,R,RS,QSUB,PTCONV,RATQSC,CLDF)
8      IMPLICIT NONE
9C     
10C--------------------------------------------------------------------------------
11C
12C Inputs:
13C
14C  ND----------: Number of vertical levels
15C  R--------ND-: Domain-averaged mixing ratio of total water
16C  RS-------ND-: Mean saturation humidity mixing ratio within the gridbox
17C  QSUB-----ND-: Mixing ratio of condensed water within clouds associated
18C                with SUBGRID-SCALE condensation processes (here, it is
19C                predicted by the convection scheme)
20C Outputs:
21C
22C  PTCONV-----ND-: Point convectif = TRUE
23C  RATQSC-----ND-: Largeur normalisee de la distribution
24C  CLDF-----ND-: Fraction nuageuse
25C
26C--------------------------------------------------------------------------------
27
28
29      INTEGER klon,ND
30      REAL R(klon,ND),  RS(klon,ND), QSUB(klon,ND)
31      LOGICAL PTCONV(klon,ND)
32      REAL RATQSC(klon,ND)
33      REAL CLDF(klon,ND)
34
35c -- parameters controlling the iteration:
36c --    nmax    : maximum nb of iterations (hopefully never reached)
37c --    epsilon : accuracy of the numerical resolution
38c --    vmax    : v-value above which we use an asymptotic expression for ERF(v)
39
40      INTEGER nmax
41      PARAMETER ( nmax = 10)
42      REAL epsilon, vmax0, vmax(klon)
43      PARAMETER ( epsilon = 0.02, vmax0 = 2.0 )
44
45      REAL min_mu, min_Q
46      PARAMETER ( min_mu =  1.e-12, min_Q=1.e-12 )
47     
48      INTEGER i,K, n, m
49      REAL mu(klon), qsat(klon), delta(klon), beta(klon)
50      real zu2(klon),zv2(klon)
51      REAL xx(klon), aux(klon), coeff(klon), block(klon)
52      REAL  dist(klon), fprime(klon), det(klon)
53      REAL pi, u(klon), v(klon), erfcu(klon), erfcv(klon)
54      REAL  xx1(klon), xx2(klon)
55      real erf,kkk
56      real sqrtpi,sqrt2,zx1,zx2,exdel
57c lconv = true si le calcul a converge (entre autre si qsub < min_q)
58       LOGICAL lconv(klon)
59
60
61      pi = ACOS(-1.)
62      sqrtpi=sqrt(pi)
63      sqrt2=sqrt(2.)
64
65      ptconv=.false.
66      ratqsc=0.
67
68
69      DO 500 K = 1, ND
70
71                                    do i=1,klon ! vector
72      mu(i) = R(i,K)
73      mu(i) = MAX(mu(i),min_mu)
74      qsat(i) = RS(i,K)
75      qsat(i) = MAX(qsat(i),min_mu)
76      delta(i) = log(mu(i)/qsat(i))
77                                    enddo ! vector
78
79C
80C ***          There is no subgrid-scale condensation;        ***
81C ***   the scheme becomes equivalent to an "all-or-nothing"  ***
82C ***             large-scale condensation scheme.            ***
83C
84
85C
86C ***     Some condensation is produced at the subgrid-scale       ***
87C ***                                                              ***
88C ***       PDF = generalized log-normal distribution (GNO)        ***
89C ***   (k<0 because a lower bound is considered for the PDF)      ***
90C ***                                                              ***
91C ***  -> Determine x (the parameter k of the GNO PDF) such        ***
92C ***  that the contribution of subgrid-scale processes to         ***
93C ***  the in-cloud water content is equal to QSUB(K)              ***
94C ***  (equations (13), (14), (15) + Appendix B of the paper)      ***
95C ***                                                              ***
96C ***    Here, an iterative method is used for this purpose        ***
97C ***    (other numerical methods might be more efficient)         ***
98C ***                                                              ***
99C ***          NB: the "error function" is called ERF              ***
100C ***                 (ERF in double precision)                   ***
101C
102
103c  On commence par eliminer les cas pour lesquels on n'a pas
104c  suffisamment d'eau nuageuse.
105
106                                    do i=1,klon ! vector
107
108      IF ( QSUB(i,K) .lt. min_Q ) THEN
109        ptconv(i,k)=.false.
110        ratqsc(i,k)=0.
111        lconv(i)  = .true.
112
113c   Rien on a deja initialise
114
115      ELSE
116
117        lconv(i)  = .FALSE.
118        vmax(i) = vmax0
119
120        beta(i) = QSUB(i,K)/mu(i) + EXP( -MIN(0.0,delta(i)) )
121
122c --  roots of equation v > vmax:
123
124        det(i) = delta(i) + vmax(i)**2.
125        if (det(i).LE.0.0) vmax(i) = vmax0 + 1.0
126        det(i) = delta(i) + vmax(i)**2.
127
128        if (det(i).LE.0.) then
129          xx(i) = -0.0001
130        else
131         zx1=-sqrt2*vmax(i)
132         zx2=SQRT(1.0+delta(i)/(vmax(i)**2.))
133         xx1(i)=zx1*(1.0-zx2)
134         xx2(i)=zx1*(1.0+zx2)
135         xx(i) = 1.01 * xx1(i)
136         if ( xx1(i) .GE. 0.0 ) xx(i) = 0.5*xx2(i)
137        endif
138        if (delta(i).LT.0.) xx(i) = -0.5*SQRT(log(2.))
139
140      ENDIF
141
142                                    enddo       ! vector
143
144c----------------------------------------------------------------------
145c   Debut des nmax iterations pour trouver la solution.
146c----------------------------------------------------------------------
147
148      DO n = 1, nmax
149
150                                    do i=1,klon ! vector
151        if (.not.lconv(i)) then
152
153          u(i) = delta(i)/(xx(i)*sqrt2) + xx(i)/(2.*sqrt2)
154          v(i) = delta(i)/(xx(i)*sqrt2) - xx(i)/(2.*sqrt2)
155
156          IF ( v(i) .GT. vmax(i) ) THEN
157
158            IF (     ABS(u(i))  .GT. vmax(i)
159     :          .AND.  delta(i) .LT. 0. ) THEN
160
161c -- use asymptotic expression of erf for u and v large:
162c ( -> analytic solution for xx )
163             exdel=beta(i)*EXP(delta(i))
164             aux(i) = 2.0*delta(i)*(1.-exdel)
165     :                       /(1.+exdel)
166             if (aux(i).lt.0.) then
167c                print*,'AUX(',i,',',k,')<0',aux(i),delta(i),beta(i)
168                aux(i)=0.
169             endif
170             xx(i) = -SQRT(aux(i))
171             block(i) = EXP(-v(i)*v(i)) / v(i) / sqrtpi
172             dist(i) = 0.0
173             fprime(i) = 1.0
174
175            ELSE
176
177c -- erfv -> 1.0, use an asymptotic expression of erfv for v large:
178
179             erfcu(i) = 1.0-ERF(u(i))
180c  !!! ATTENTION : rajout d'un seuil pour l'exponentiel
181             aux(i) = sqrtpi*erfcu(i)*EXP(min(v(i)*v(i),100.))
182             coeff(i) = 1.0 - 1./2./(v(i)**2.) + 3./4./(v(i)**4.)
183             block(i) = coeff(i) * EXP(-v(i)*v(i)) / v(i) / sqrtpi
184             dist(i) = v(i) * aux(i) / coeff(i) - beta(i)
185             fprime(i) = 2.0 / xx(i) * (v(i)**2.)
186     :           * ( coeff(i)*EXP(-delta(i)) - u(i) * aux(i) )
187     :           / coeff(i) / coeff(i)
188           
189            ENDIF ! ABS(u)
190
191          ELSE
192
193c -- general case:
194
195           erfcu(i) = 1.0-ERF(u(i))
196           erfcv(i) = 1.0-ERF(v(i))
197           block(i) = erfcv(i)
198           dist(i) = erfcu(i) / erfcv(i) - beta(i)
199           zu2(i)=u(i)*u(i)
200           zv2(i)=v(i)*v(i)
201           if(zu2(i).gt.20..or. zv2(i).gt.20.) then
202c              print*,'ATTENTION !!! xx(',i,') =', xx(i)
203c           print*,'ATTENTION !!! klon,ND,R,RS,QSUB,PTCONV,RATQSC,CLDF',
204c     .klon,ND,R(i,k),RS(i,k),QSUB(i,k),PTCONV(i,k),RATQSC(i,k),
205c     .CLDF(i,k)
206c              print*,'ATTENTION !!! zu2 zv2 =',zu2(i),zv2(i)
207              zu2(i)=20.
208              zv2(i)=20.
209             fprime(i) = 0.
210           else
211             fprime(i) = 2. /sqrtpi /xx(i) /erfcv(i)**2.
212     :           * (   erfcv(i)*v(i)*EXP(-zu2(i))
213     :               - erfcu(i)*u(i)*EXP(-zv2(i)) )
214           endif
215          ENDIF ! x
216
217c -- test numerical convergence:
218
219c         print*,'avant test ',i,k,lconv(i),u(i),v(i)
220          if ( ABS(dist(i)/beta(i)) .LT. epsilon ) then
221c           print*,'v-u **2',(v(i)-u(i))**2
222c           print*,'exp v-u **2',exp((v(i)-u(i))**2)
223            ptconv(i,K) = .TRUE.
224            lconv(i)=.true.
225c  borne pour l'exponentielle
226            ratqsc(i,k)=min(2.*(v(i)-u(i))**2,20.)
227            ratqsc(i,k)=sqrt(exp(ratqsc(i,k))-1.)
228            CLDF(i,K) = 0.5 * block(i)
229          else
230            xx(i) = xx(i) - dist(i)/fprime(i)
231          endif
232c         print*,'apres test ',i,k,lconv(i)
233
234        endif ! lconv
235                                    enddo       ! vector
236
237c----------------------------------------------------------------------
238c   Fin des nmax iterations pour trouver la solution.
239        ENDDO ! n
240c----------------------------------------------------------------------
241
242500   CONTINUE  ! K
243
244       RETURN
245       END
246
247
248
Note: See TracBrowser for help on using the repository browser.