source: LMDZ6/trunk/libf/phylmd/clouds_gno.f90 @ 5821

Last change on this file since 5821 was 5816, checked in by rkazeroni, 2 months ago

For GPU porting of clouds_gno and clouds_bigauss routines:

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