source: trunk/LMDZ.GENERIC/libf/phystd/thermcell_plume.F90 @ 2080

Last change on this file since 2080 was 2072, checked in by aslmd, 7 years ago

ioipsl is not used in thermcell_main et thermcell_plume

File size: 23.2 KB
Line 
1!
2!
3!
4      SUBROUTINE thermcell_plume(itap,ngrid,klev,ptimestep,ztv,               &
5      &                    zthl,po,zl,rhobarz,zlev,pplev,pphi,zpspsk,         &
6      &                    alim_star,alim_star_tot,lalim,f0,detr_star,        &
7      &                    entr_star,f_star,ztva,ztla,zqla,zqta,zha,          &
8      &                    zw2,w_est,ztva_est,zqsatth,lmix,lmix_bis,          &
9      &                    lmin,lev_out,lunout1,igout)
10     
11     
12!==============================================================================
13! thermcell_plume: calcule les valeurs de qt, thetal et w dans l ascendance
14! AB : ql means "liquid water mass mixing ratio"
15!      qt means "total water mass mixing ratio"
16!      TP means "potential temperature"
17!      TRPV means "virtual potential temperature with latent heat release" 
18!      TPV means "virtual potential temperature"
19!      TR means "temperature with latent heat release"
20!==============================================================================
21     
22      USE print_control_mod, ONLY: prt_level
23      USE watercommon_h, ONLY: RLvCp, RETV, Psat_water
24      USE thermcell_mod
25     
26      IMPLICIT NONE
27     
28     
29!==============================================================================
30! Declaration
31!==============================================================================
32     
33!      inputs:
34!      -------
35     
36      INTEGER itap
37      INTEGER ngrid
38      INTEGER klev
39      INTEGER lunout1
40      INTEGER igout
41      INTEGER lev_out                           ! niveau pour les print
42     
43      REAL ptimestep                            ! time step
44      REAL ztv(ngrid,klev)                      ! TRPV environment
45      REAL zthl(ngrid,klev)                     ! TP   environment
46      REAL po(ngrid,klev)                       ! qt   environment
47      REAL zl(ngrid,klev)                       ! ql   environment
48      REAL rhobarz(ngrid,klev)                  ! levels density
49      REAL zlev(ngrid,klev+1)                   ! levels altitude
50      REAL pplev(ngrid,klev+1)                  ! levels pressure
51      REAL pphi(ngrid,klev)                     ! geopotential
52      REAL zpspsk(ngrid,klev)                   ! Exner function
53     
54!      outputs:
55!      --------
56     
57      INTEGER lmin(ngrid)                       ! plume base level (first unstable level)
58      INTEGER lalim(ngrid)                      ! higher alimentation level
59      INTEGER lmix(ngrid)                       ! maximum vertical speed level
60      INTEGER lmix_bis(ngrid)                   ! maximum vertical speed level (modified)
61     
62      REAL alim_star(ngrid,klev)                ! normalized alimentation
63      REAL alim_star_tot(ngrid)                 ! integrated alimentation
64     
65      REAL f0(ngrid)                            ! previous time step mass flux norm
66     
67      REAL detr_star(ngrid,klev)                ! normalized detrainment
68      REAL entr_star(ngrid,klev)                ! normalized entrainment
69      REAL f_star(ngrid,klev+1)                 ! normalized mass flux
70     
71      REAL ztva(ngrid,klev)                     ! TRPV plume (after mixing)
72      REAL ztva_est(ngrid,klev)                 ! TRPV plume (before mixing)
73      REAL ztla(ngrid,klev)                     ! TP   plume
74      REAL zqla(ngrid,klev)                     ! ql   plume (after mixing)
75      REAL zqta(ngrid,klev)                     ! qt   plume
76      REAL zha(ngrid,klev)                      ! TRPV plume
77     
78      REAL w_est(ngrid,klev+1)                  ! updraft square vertical speed (before mixing)
79      REAL zw2(ngrid,klev+1)                    ! updraft square vertical speed (after mixing)
80     
81      REAL zqsatth(ngrid,klev)                  ! saturation vapor pressure (after mixing)
82     
83!      local:
84!      ------
85     
86      INTEGER ig, l, k
87      INTEGER lt
88      INTEGER lm
89     
90      REAL zqla_est(ngrid,klev)                 ! ql   plume (before mixing)
91      REAL zta_est(ngrid,klev)                  ! TR   plume (before mixing)
92      REAL zbuoy(ngrid,klev)                    ! plume buoyancy
93      REAL zbuoyjam(ngrid,klev)                 ! plume buoyancy (modified)
94     
95      REAL ztemp(ngrid)                         ! temperature for saturation vapor pressure computation in plume
96      REAL zqsat(ngrid)                         ! saturation vapor pressure (before mixing)
97      REAL zdz                                  ! layers height
98     
99      REAL zalpha                               !
100      REAL zdqt(ngrid,klev)                     !
101      REAL zbetalpha                            !
102      REAL zdw2                                 !
103      REAL zdw2bis                              !
104      REAL zw2fact                              !
105      REAL zw2factbis                           !
106      REAL zw2m                                 !
107      REAL zdzbis                               !
108      REAL coefzlmel                            !
109      REAL zdz2                                 !
110      REAL zdz3                                 !
111      REAL lmel                                 !
112      REAL zlmel                                !
113      REAL zlmelup                              !
114      REAL zlmeldwn                             !
115      REAL zlt                                  !
116      REAL zltdwn                               !
117      REAL zltup                                ! useless here
118     
119      REAL dummy
120     
121      LOGICAL active(ngrid)                     ! if the plume is active at ig,l (speed and incoming mass flux > 0 or l=lmin)
122      LOGICAL activetmp(ngrid)                  ! if the plus is active at ig,l (active=true and outgoing mass flux > 0)
123      LOGICAL, SAVE :: first = .true.           ! if it is the first time step
124     
125!$OMP THREADPRIVATE(first)
126     
127!==============================================================================
128! Initialization
129!==============================================================================
130     
131      zbetalpha = betalpha / (1. + betalpha)
132     
133      ztva(:,:)        = ztv(:,:)               ! ztva     is set to the virtual potential temperature without latent heat release
134      ztva_est(:,:)    = ztva(:,:)              ! ztva_est is set to the virtual potential temperature without latent heat release
135      ztla(:,:)        = zthl(:,:)              ! ztla     is set to the potential temperature
136      zqta(:,:)        = po(:,:)                ! zqta     is set to qt
137      zqla(:,:)        = 0.                     ! zqla     is set to ql
138      zqla_est(:,:)    = 0.                     ! zqla_est is set to ql
139      zha(:,:)         = ztva(:,:)              ! zha      is set to the plume virtual potential temperature without latent heat release
140     
141      zqsat(:)         = 0.
142      zqsatth(:,:)     = 0.
143     
144      w_est(:,:)       = 0.
145      zw2(:,:)         = 0.
146     
147      zbuoy(:,:)       = 0.
148      zbuoyjam(:,:)    = 0.
149     
150      f_star(:,:)      = 0.
151      detr_star(:,:)   = 0.
152      entr_star(:,:)   = 0.
153      alim_star(:,:)   = 0.
154      alim_star_tot(:) = 0.
155     
156      lmix(:)          = 1
157      lmix_bis(:)      = 2
158      lalim(:)         = 1
159      lmin(:)          = linf
160     
161!==============================================================================
162! 0. Calcul de l'alimentation
163!==============================================================================
164     
165!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
166! AB : Convective plumes can go off from every layer above the linf-th and
167!      where pressure is lesser than pres_limit (cf. thermcell_plume).
168!      The second constraint is added to avoid the parametrization occurs too
169!      high when the low atmosphere is stable.
170!      However, once there is a triggered plume, it can rise as high as its
171!      velocity allows it (it can overshoot).
172!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
173      DO ig=1,ngrid
174         active(ig) = .false.
175         l = linf
176         DO WHILE ((.not.active(ig)) .and. pplev(ig,l+1).gt.pres_limit .and. l.lt.klev)
177            IF (ztv(ig,l).gt.ztv(ig,l+1)) THEN
178               active(ig) = .true.
179               lmin(ig) = l
180            ENDIF
181            l = l + 1
182         ENDDO
183      ENDDO
184     
185!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
186! AB : On pourrait n'appeler thermcell_alim que si la plume est active
187!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
188      CALL thermcell_alim(ngrid,klev,ztv,zlev,alim_star,lalim,lmin)
189     
190!==============================================================================
191! 1. Calcul dans la premiere couche
192!==============================================================================
193     
194      DO ig=1,ngrid
195         IF (active(ig)) THEN
196           
197!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
198! AB : plume takes the environment features for every layer below lmin.
199!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
200            DO l=1,lmin(ig)
201               ztla(ig,l) = zthl(ig,l)
202               zqta(ig,l) = po(ig,l)
203               zqla(ig,l) = zl(ig,l)
204            ENDDO
205           
206            l = lmin(ig)
207            f_star(ig,l+1) = alim_star(ig,l)
208           
209            zw2(ig,l+1) = 2. * RG * (zlev(ig,l+1) - zlev(ig,l))               &
210            &                * (ztv(ig,l) - ztv(ig,l+1)) / ztv(ig,l+1)
211           
212            w_est(ig,l+1) = zw2(ig,l+1)
213           
214         ENDIF
215      ENDDO
216     
217!==============================================================================
218! 2. Boucle de calcul de la vitesse verticale dans le thermique
219!==============================================================================
220     
221      DO l=2,klev-1
222         
223!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
224! AB : we decide here if the plume is still active or not. When the plume's
225!      first level is reached, we set active to "true". Otherwise, it is given
226!      by zw2, f_star, alim_star and entr_star.
227!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
228         DO ig=1,ngrid
229            IF (l==lmin(ig)+1) THEN
230               active(ig) = .true.
231            ENDIF
232           
233            active(ig) = active(ig)                                           &
234            &            .and. zw2(ig,l)>1.e-10                               &
235            &            .and. f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)>1.e-10
236         ENDDO
237         
238         ztemp(:) = zpspsk(:,l) * ztla(:,l-1)
239         
240         DO ig=1,ngrid
241            CALL Psat_water(ztemp(ig), pplev(ig,l), dummy, zqsat(ig))
242         ENDDO
243         
244!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
245! AB : we compute thermodynamical values and speed in the plume in the layer l
246!      without mixing with environment.
247!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
248         
249         DO ig=1,ngrid
250            IF (active(ig)) THEN
251               zqla_est(ig,l) = max(0.,zqta(ig,l-1)-zqsat(ig))                   ! zqla_est set to ql   plume
252               ztva_est(ig,l) = ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*zqla_est(ig,l)   ! ztva_est set to TR   plume
253               zta_est(ig,l)  = ztva_est(ig,l)                                   ! zta_est  set to TR   plume
254               ztva_est(ig,l) = ztva_est(ig,l)/zpspsk(ig,l)                      ! ztva_est set to TRP  plume
255               ztva_est(ig,l) = ztva_est(ig,l)*(1.+RETV*(zqta(ig,l-1)         &  ! ztva_est set to TRPV plume
256               &              - zqla_est(ig,l))-zqla_est(ig,l))
257               
258               zbuoy(ig,l) = RG * (ztva_est(ig,l)-ztv(ig,l)) / ztv(ig,l)
259               zdz = zlev(ig,l+1) - zlev(ig,l)
260               
261!==============================================================================
262! 3. Calcul de la flotabilite modifiee par melange avec l'air au dessus
263!==============================================================================
264               
265               lmel = fact_thermals_ed_dz * zlev(ig,l)
266               zlmel = zlev(ig,l) + lmel
267               lt = l + 1
268               zlt = zlev(ig,lt)
269               zdz2 = zlev(ig,lt) - zlev(ig,l)
270               
271               DO while (lmel.gt.zdz2)
272                  lt   = lt + 1
273                  zlt  = zlev(ig,lt)
274                  zdz2 = zlev(ig,lt) - zlev(ig,l)
275               ENDDO
276               
277!               IF (lt-l.gt.1) THEN
278!                  print *, 'WARNING: lt is greater than l+1!'
279!                  print *, 'l,lt', l, lt
280!               ENDIF
281               
282               zdz3 = zlev(ig,lt+1) - zlt
283               zltdwn = zlev(ig,lt) - zdz3 / 2
284               zlmelup = zlmel + (zdz / 2)
285               coefzlmel = Min(1.,(zlmelup - zltdwn) / zdz)
286               
287               zbuoyjam(ig,l) = 1.* RG * (coefzlmel *                         &
288               &                (ztva_est(ig,l) - ztv(ig,lt)) / ztv(ig,lt)    &
289               &              + (1. - coefzlmel) *                            &
290               &                (ztva_est(ig,l) - ztv(ig,lt-1)) / ztv(ig,lt-1)) &
291               &              + 0. * zbuoy(ig,l)
292               
293!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
294! AB : initial formulae
295!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
296!               zw2fact = fact_epsilon * 2. * zdz / (1. + betalpha)
297!               zdw2 = afact * zbuoy(ig,l) / fact_epsilon
298!               zdw2bis = afact * zbuoy(ig,l-1) / fact_epsilon
299!               w_est(ig,l+1) = Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2)+zdw2)
300!               w_est(ig,l+1) = Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2bis)+zdw2)
301!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
302! AB : own derivation for w_est (Rio 2010 formula with e=d=0)
303!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
304               zw2fact = 2. * fact_epsilon * zdz
305               zdw2 = 2. * afact * zbuoy(ig,l) * zdz
306               w_est(ig,l+1) = Max(0., exp(-zw2fact) * w_est(ig,l) + zdw2)
307               
308!               IF (w_est(ig,l+1).le.0.) THEN
309!                  print *, 'WARNING: w_est is negative!'
310!                  print *, 'l,w_est', l+1, w_est(ig,l+1)
311!               ENDIF
312            ENDIF
313         ENDDO
314         
315!==============================================================================
316! 4. Calcul de l'entrainement et du detrainement
317!==============================================================================
318         
319         DO ig=1,ngrid
320            IF (active(ig)) THEN
321               
322               zdz = zlev(ig,l+1) - zlev(ig,l)
323               
324!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
325! AB : The next test is added to avoid divisions by zero when w_est vanishes.
326!      Indeed, entr and detr computed here are of no importance because w_est
327!      <= 0 means it will be the last layer reached by the plume and then they
328!      will be reset in thermcell_flux.
329!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
330               IF (w_est(ig,l+1).eq.0.) THEN
331                  zw2m = 1.
332                  zalpha = 0.
333               ELSE
334                  zw2m = w_est(ig,l+1)
335                  zalpha = f0(ig) * f_star(ig,l) / sqrt(w_est(ig,l+1)) / rhobarz(ig,l)
336               ENDIF
337               
338!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
339! AB : The next test is added to avoid a division by zero if there is no water
340!      in the environment.
341!      In the case where there is no water in the env. but water in the plume
342!      (ascending from depth) we set the effect on detrainment equal to zero
343!      but at the next time step, po will be positive thanks to the mixing and
344!      then the physical effect of the water gradient will be taken on board.
345!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
346               IF (po(ig,l).lt.1.e-6) THEN
347!                  print *, 'WARNING: po=0 in layer',l,'!'
348!                  print *, 'po,zqta', po(ig,l), zqta(ig,l-1)
349                  zdqt(ig,l) = 0.0
350               ELSE
351                  zdqt(ig,l) = max(zqta(ig,l-1)-po(ig,l),0.) / po(ig,l)
352               ENDIF
353               
354!------------------------------------------------------------------------------
355! Detrainment
356!------------------------------------------------------------------------------
357               
358               detr_star(ig,l) = f_star(ig,l) * zdz * (                       &
359               &                 mix0 * 0.1 / (zalpha + 0.001)                &
360               &               + MAX(detr_min,                                &
361               &                 -afact * zbetalpha * zbuoyjam(ig,l) / zw2m   &
362               &               + detr_q_coef*(zdqt(ig,l)/zw2m)**detr_q_power) )
363               
364!               IF (detr_star(ig,l).lt.0.) THEN
365!                  print *, 'WARNING: detrainment is negative!'
366!                  print *, 'l,detr', l, detr_star(ig,l)
367!               ENDIF
368               
369!------------------------------------------------------------------------------
370! Entrainment
371!------------------------------------------------------------------------------
372               
373               entr_star(ig,l) = f_star(ig,l) * zdz * (                       &
374               &                 mix0 * 0.1 / (zalpha+0.001)                  &
375               &               + MAX(entr_min,                                &
376               &                 zbetalpha * afact * zbuoyjam(ig,l) / zw2m    &
377               &               - zbetalpha * fact_epsilon) )
378               
379!               IF (entr_star(ig,l).lt.0.) THEN
380!                  print *, 'WARNING: entrainment is negative!'
381!                  print *, 'l,entr', l, entr_star(ig,l)
382!               ENDIF
383               
384!------------------------------------------------------------------------------
385! Alimentation and entrainment
386!------------------------------------------------------------------------------
387               
388               IF (l.lt.lalim(ig)) THEN
389                  alim_star(ig,l) = max(alim_star(ig,l),entr_star(ig,l))
390                  entr_star(ig,l) = 0.
391               ENDIF
392               
393!------------------------------------------------------------------------------
394! Mass flux
395!------------------------------------------------------------------------------
396               
397               f_star(ig,l+1) = f_star(ig,l) + alim_star(ig,l)                &
398               &              + entr_star(ig,l) - detr_star(ig,l)
399               
400!               IF (f_star(ig,l+1).le.0.) THEN
401!                  print *, 'WARNING: mass flux is negative!'
402!                  print *, 'l,f_star', l+1, f_star(ig,l+1)
403!               ENDIF
404               
405            ENDIF
406         ENDDO
407         
408!==============================================================================
409! 5. Calcul de la vitesse verticale en melangeant Tl et qt du thermique
410!==============================================================================
411         
412         activetmp(:) = active(:) .and. f_star(:,l+1)>1.e-10
413         
414!------------------------------------------------------------------------------
415! Calcul du melange avec l'environnement
416!------------------------------------------------------------------------------
417         
418         DO ig=1,ngrid
419            IF (activetmp(ig)) THEN
420               ztla(ig,l) = (f_star(ig,l) * ztla(ig,l-1)                      &  ! ztla is set to TP in plume (mixed)
421               &          + (alim_star(ig,l) + entr_star(ig,l)) * zthl(ig,l)) &
422               &          / (f_star(ig,l+1) + detr_star(ig,l))
423               zqta(ig,l) = (f_star(ig,l) * zqta(ig,l-1) +                    &  ! zqta is set to qt in plume (mixed)
424               &          + (alim_star(ig,l) + entr_star(ig,l)) * po(ig,l))   &
425               &          / (f_star(ig,l+1) + detr_star(ig,l))
426            ENDIF
427         ENDDO
428         
429         ztemp(:) = zpspsk(:,l) * ztla(:,l)
430         
431         DO ig=1,ngrid
432            IF (activetmp(ig)) THEN
433               CALL Psat_water(ztemp(ig), pplev(ig,l), dummy, zqsatth(ig,l))
434            ENDIF
435         ENDDO
436         
437!------------------------------------------------------------------------------
438! Calcul de la vitesse verticale zw2 apres le melange
439!------------------------------------------------------------------------------
440         
441         DO ig=1,ngrid
442            IF (activetmp(ig)) THEN
443               zqla(ig,l) = max(0.,zqta(ig,l)-zqsatth(ig,l))                     ! zqla is set to ql   plume (mixed)
444               ztva(ig,l) = ztla(ig,l) * zpspsk(ig,l)+RLvCp*zqla(ig,l)           ! ztva is set to TR   plume (mixed)
445               ztva(ig,l) = ztva(ig,l) / zpspsk(ig,l)                            ! ztva is set to TRP  plume (mixed)
446               zha(ig,l)  = ztva(ig,l)                                           ! zha  is set to TRP  plume (mixed)
447               ztva(ig,l) = ztva(ig,l) * (1. + RETV*(zqta(ig,l)-zqla(ig,l))   &  ! ztva is set to TRPV plume (mixed)
448               &                             - zqla(ig,l))
449               
450               zbuoy(ig,l) = RG * (ztva(ig,l) - ztv(ig,l)) / ztv(ig,l)
451               zdz = zlev(ig,l+1) - zlev(ig,l)
452               
453!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
454! AB : initial formula
455!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
456!               zw2fact = fact_epsilon * 2. * zdz / (1. + betalpha)
457!               zdw2 = afact * zbuoy(ig,l) / fact_epsilon
458!               zdw2bis = afact * zbuoy(ig,l-1) / fact_epsilon
459!               zw2(ig,l+1) = Max(0.0001,exp(-zw2fact)*(zw2(ig,l)-zdw2)+zdw2)
460!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
461! AB : own derivation for zw2 (Rio 2010 formula)
462!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
463               zw2fact = 2. * (fact_epsilon * zdz  + entr_star(ig,l) / f_star(ig,l))
464               zdw2 = 2. * afact * zbuoy(ig,l) * zdz
465               zw2(ig,l+1) = Max(0., exp(-zw2fact) * zw2(ig,l) + zdw2)
466               
467!               IF (zw2(ig,l+1).le.0.) THEN
468!                  print *, 'WARNING: zw2 is negative!'
469!                  print *, 'l,zw2', l+1, zw2(ig,l+1)
470!               ENDIF
471            ENDIF
472         ENDDO
473         
474      ENDDO
475     
476!==============================================================================
477! 6. New computation of alim_star_tot
478!==============================================================================
479     
480      DO ig=1,ngrid
481         alim_star_tot(ig) = 0.
482      ENDDO
483     
484      DO ig=1,ngrid
485         DO l=1,lalim(ig)-1
486            alim_star_tot(ig) = alim_star_tot(ig) + alim_star(ig,l)
487         ENDDO
488      ENDDO
489     
490#undef wrgrads_thermcell
491#ifdef wrgrads_thermcell
492      call wrgradsfi(1,klev,entr_star(igout,1:klev),'esta    ','esta    ')
493      call wrgradsfi(1,klev,detr_star(igout,1:klev),'dsta    ','dsta    ')
494      call wrgradsfi(1,klev,zbuoy(igout,1:klev)    ,'buoy    ','buoy    ')
495      call wrgradsfi(1,klev,zdqt(igout,1:klev)     ,'dqt     ','dqt     ')
496      call wrgradsfi(1,klev,w_est(igout,1:klev)    ,'w_est   ','w_est   ')
497      call wrgradsfi(1,klev,w_est(igout,2:klev+1)  ,'w_es2   ','w_es2   ')
498      call wrgradsfi(1,klev,zw2(igout,1:klev)      ,'zw2A    ','zw2A    ')
499#endif
500     
501     
502RETURN
503END
Note: See TracBrowser for help on using the repository browser.