source: trunk/LMDZ.MARS/libf/phymars/calltherm_mars.F90 @ 289

Last change on this file since 289 was 284, checked in by acolaitis, 14 years ago

--- AC 07/09/2011 ---

  • Added new flag for the Richardson-based surface layer :

callrichsl, can be changed in callphys.def

One should always use the thermals model when using this surface layer model.
Somes cases (weakly unstable with low winds), when not using thermals, won't be well represented by the
Richardson surface layer. This stands for Mesoscale and Gcm but not for LES model.

Correct configs :

callrichsl = .true.
calltherm = .true.

callrichsl = .false.
calltherm = .false.

callrichsl = .false.
calltherm = .true.

Previously unstable config :

callrichsl = .true.
calltherm = .false.

  • To be able to run without thermals and with the new surface layer, a modification has been made to

physiq.F to account for gustiness in GCM and MESOSCALE for negative Richardson, so that :

callrichsl = .true.
calltherm = .false.

can now be used without problems, but is not recommended.

  • Consequently, callrichsl = .false. is now the default configuration for thermals.

We recall the available options in callphys.def for thermals :

outptherm = BOOLEAN (.false. by default) : outputs thermals related quantities (lots of diagfi)
nsplit_thermals = INTEGER (50 by default in gcm, 2 in mesoscale) : subtimestep for thermals model.

It is recommended to use at least 40 in the gcm, and at least 2 in the mesoscale.
The user can lower these values but should check it's log for anomalies or errors regarding
tracer transport in the thermals, or "granulosity" in the outputs for wmax, lmax and hfmax.


File size: 6.9 KB
Line 
1!
2! $Id: calltherm.F90 1428 2010-09-13 08:43:37Z fairhead $
3!
4      subroutine calltherm_mars(dtime,zzlev,zzlay  &
5     &      ,pplay,paprs,pphi  &
6     &      ,u_seri,v_seri,t_seri,pq_therm,q2_therm  &
7     &      ,d_u_ajs,d_v_ajs,d_t_ajs,d_q_ajs,dq2_therm  &
8     &      ,fm_therm,entr_therm,detr_therm,lmax,zmax,&
9     &   zw2,fraca,zpopsk,ztla,heatFlux,heatFlux_down,&
10     &     buoyancyOut,buoyancyEst,hfmax,wmax)
11
12       USE ioipsl_getincom
13      implicit none
14
15#include "dimensions.h"
16#include "dimphys.h"
17
18      REAL dtime
19      LOGICAL logexpr0, logexpr2(ngridmx,nlayermx), logexpr1(ngridmx)
20      REAL fact
21      INTEGER nbptspb
22
23      REAL, INTENT(IN) :: zzlay(ngridmx,nlayermx)
24      REAL, INTENT(IN) :: zzlev(ngridmx,nlayermx+1)
25
26      REAL u_seri(ngridmx,nlayermx),v_seri(ngridmx,nlayermx)
27      REAL t_seri(ngridmx,nlayermx),pq_therm(ngridmx,nlayermx,nqmx)
28      REAL q2_therm(ngridmx,nlayermx)
29      REAL paprs(ngridmx,nlayermx+1)
30      REAL pplay(ngridmx,nlayermx)
31      REAL pphi(ngridmx,nlayermx)
32      real zlev(ngridmx,nlayermx+1)
33!test: on sort lentr et a* pour alimenter KE
34      REAL zw2(ngridmx,nlayermx+1),fraca(ngridmx,nlayermx+1)
35      REAL zzw2(ngridmx,nlayermx+1)
36
37!FH Update Thermiques
38      REAL d_t_ajs(ngridmx,nlayermx), d_q_ajs(ngridmx,nlayermx,nqmx)
39      REAL d_u_ajs(ngridmx,nlayermx),d_v_ajs(ngridmx,nlayermx)
40      REAL dq2_therm(ngridmx,nlayermx), dq2_the(ngridmx,nlayermx)
41      real fm_therm(ngridmx,nlayermx+1)
42      real entr_therm(ngridmx,nlayermx),detr_therm(ngridmx,nlayermx)
43
44!********************************************************
45!     declarations
46      real zpopsk(ngridmx,nlayermx)
47      real ztla(ngridmx,nlayermx)
48      real wmax(ngridmx)
49      real hfmax(ngridmx)
50      integer lmax(ngridmx)
51      real zmax(ngridmx)
52
53!nouvelles variables pour la convection
54!RC
55      !on garde le zmax du pas de temps precedent
56!********************************************************
57
58
59! variables locales
60      REAL d_t_the(ngridmx,nlayermx), d_q_the(ngridmx,nlayermx,nqmx)
61      REAL d_u_the(ngridmx,nlayermx),d_v_the(ngridmx,nlayermx)
62!
63      integer isplit,nsplit_thermals
64      real r_aspect_thermals
65
66      real zfm_therm(ngridmx,nlayermx+1),zdt
67      real zentr_therm(ngridmx,nlayermx),zdetr_therm(ngridmx,nlayermx)
68      real heatFlux(ngridmx,nlayermx)
69      real heatFlux_down(ngridmx,nlayermx)
70      real buoyancyOut(ngridmx,nlayermx)
71      real buoyancyEst(ngridmx,nlayermx)
72      real zheatFlux(ngridmx,nlayermx)
73      real zheatFlux_down(ngridmx,nlayermx)
74      real zbuoyancyOut(ngridmx,nlayermx)
75      real zbuoyancyEst(ngridmx,nlayermx)
76
77      character (len=20) :: modname='calltherm'
78      character (len=80) :: abort_message
79
80      integer i,k
81      logical, save :: first=.true.
82
83      REAL tstart,tstop
84
85
86!  Modele du thermique
87!  ===================
88 
89!         r_aspect_thermals     ! ultimately conrols the amount of mass going through the thermals
90                                ! decreasing it increases the thermals effect. Tests at gcm resolution
91                                ! shows that too low values destabilize the model
92                                ! when changing this value, one should check that the surface layer model
93                                ! outputs the correct Cd*u and Ch*u through changing the gustiness coefficient beta
94
95
96#ifdef MESOSCALE
97         !! valid for timesteps < 200s
98         nsplit_thermals=2
99         r_aspect_thermals=0.7
100#else
101         nsplit_thermals=50
102         r_aspect_thermals=2.
103#endif
104
105         call getin("nsplit_thermals",nsplit_thermals)
106
107         fm_therm(:,:)=0.
108         detr_therm(:,:)=0.
109         entr_therm(:,:)=0.
110
111         heatFlux(:,:)=0.
112         heatFlux_down(:,:)=0.
113         buoyancyOut(:,:)=0.
114         buoyancyEst(:,:)=0.
115
116         zw2(:,:)=0.
117
118         zdt=dtime/REAL(nsplit_thermals)
119
120         do isplit=1,nsplit_thermals
121
122!         call cpu_time(tstart)
123
124
125! On reinitialise les flux de masse a zero pour le cumul en
126! cas de splitting
127
128         zfm_therm(:,:)=0.
129         zentr_therm(:,:)=0.
130         zdetr_therm(:,:)=0.
131
132         zheatFlux(:,:)=0.
133         zheatFlux_down(:,:)=0.
134         zbuoyancyOut(:,:)=0.
135         zbuoyancyEst(:,:)=0.
136
137         zzw2(:,:)=0.
138
139         d_t_the(:,:)=0.
140         d_u_the(:,:)=0.
141         d_v_the(:,:)=0.
142         dq2_the(:,:)=0.
143         if (nqmx .ne. 0) then
144            d_q_the(:,:,:)=0.
145         endif
146
147             CALL thermcell_main_mars(zdt  &
148     &      ,pplay,paprs,pphi,zzlev,zzlay  &
149     &      ,u_seri,v_seri,t_seri,pq_therm,q2_therm  &
150     &      ,d_u_the,d_v_the,d_t_the,d_q_the,dq2_the  &
151     &      ,zfm_therm,zentr_therm,zdetr_therm,lmax,zmax  &
152     &      ,r_aspect_thermals &
153     &      ,zzw2,fraca,zpopsk &
154     &      ,ztla,zheatFlux,zheatFlux_down &
155     &      ,zbuoyancyOut,zbuoyancyEst)
156
157      fact=1./REAL(nsplit_thermals)
158!  transformation de la derivee en tendance
159
160            d_t_the(:,:)=d_t_the(:,:)*dtime*fact
161            d_u_the(:,:)=d_u_the(:,:)*fact
162            d_v_the(:,:)=d_v_the(:,:)*fact
163            dq2_the(:,:)=dq2_the(:,:)*fact           
164
165            if (nqmx .ne. 0) then
166               d_q_the(:,:,:)=d_q_the(:,:,:)*fact
167            endif
168
169            fm_therm(:,:)=fm_therm(:,:)  &
170     &      +zfm_therm(:,:)*fact
171            entr_therm(:,:)=entr_therm(:,:)  &
172     &       +zentr_therm(:,:)*fact
173            detr_therm(:,:)=detr_therm(:,:)  &
174     &       +zdetr_therm(:,:)*fact
175
176            heatFlux(:,:)=heatFlux(:,:) &
177     &       +zheatFlux(:,:)*fact
178            heatFlux_down(:,:)=heatFlux_down(:,:) &
179     &       +zheatFlux_down(:,:)*fact
180            buoyancyOut(:,:)=buoyancyOut(:,:) &
181     &       +zbuoyancyOut(:,:)*fact
182            buoyancyEst(:,:)=buoyancyEst(:,:) &
183     &       +zbuoyancyEst(:,:)*fact
184
185            zw2(:,:)=zw2(:,:) + zzw2(:,:)*fact
186
187!  accumulation de la tendance
188     
189            d_t_ajs(:,:)=d_t_ajs(:,:)+d_t_the(:,:)
190            d_u_ajs(:,:)=d_u_ajs(:,:)+d_u_the(:,:)
191            d_v_ajs(:,:)=d_v_ajs(:,:)+d_v_the(:,:)
192            d_q_ajs(:,:,:)=d_q_ajs(:,:,:)+d_q_the(:,:,:)
193            dq2_therm(:,:)=dq2_therm(:,:)+dq2_the(:,:)
194!  incrementation des variables meteo
195     
196            t_seri(:,:) = t_seri(:,:) + d_t_the(:,:)
197            u_seri(:,:) = u_seri(:,:) + d_u_the(:,:)
198            v_seri(:,:) = v_seri(:,:) + d_v_the(:,:)
199            pq_therm(:,:,:) = pq_therm(:,:,:) + d_q_the(:,:,:)
200            q2_therm(:,:) = q2_therm(:,:) + dq2_therm(:,:)
201
202
203!         call cpu_time(tstop)
204!         print*,'elapsed time in thermals : ',tstop-tstart
205
206         enddo ! isplit
207
208     
209!****************************************************************
210
211!          do i=1,ngridmx
212!             do k=1,nlayermx
213!                if (ztla(i,k) .lt. 1.e-10) fraca(i,k) =0.
214!               print*,'youpi je sers a quelque chose !'
215!             enddo
216!          enddo
217       
218          DO i=1,ngridmx
219            hfmax(i)=MAXVAL(heatFlux(i,:)+heatFlux_down(i,:))
220            wmax(i)=MAXVAL(zw2(i,:))
221          ENDDO
222 
223      return
224
225      end
Note: See TracBrowser for help on using the repository browser.