source: trunk/LMDZ.MARS/libf/phymars/calltherm_interface.F90 @ 288

Last change on this file since 288 was 284, checked in by acolaitis, 13 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: 7.7 KB
Line 
1!
2! AC 2011-01-05
3!
4      SUBROUTINE calltherm_interface (firstcall, &
5     & long,lati,zzlev,zzlay, &
6     & ptimestep,pu,pv,pt,pq,pdu,pdv,pdt,pdq,q2, &
7     & pplay,pplev,pphi,zpopsk, &
8     & pdu_th,pdv_th,pdt_th,pdq_th,lmax_th,zmax_th,pbl_dtke,hfmax,wmax)
9
10       USE ioipsl_getincom
11
12      implicit none
13#include "callkeys.h"
14#include "dimensions.h"
15#include "dimphys.h"
16
17!--------------------------------------------------------
18! Variables d'entree
19!--------------------------------------------------------
20
21      REAL, INTENT(IN) :: ptimestep
22      REAL, INTENT(IN) :: pplev(ngridmx,nlayermx+1),pplay(ngridmx,nlayermx)
23      REAL, INTENT(IN) :: pphi(ngridmx,nlayermx)
24      REAL, INTENT(IN) :: pu(ngridmx,nlayermx),pv(ngridmx,nlayermx)
25      REAL, INTENT(IN) :: pt(ngridmx,nlayermx),pq(ngridmx,nlayermx,nqmx)
26      REAL, INTENT(IN) :: zzlay(ngridmx,nlayermx)
27      REAL, INTENT(IN) :: zzlev(ngridmx,nlayermx+1)
28      LOGICAL, INTENT(IN) :: firstcall
29      REAL, INTENT(IN) :: pdu(ngridmx,nlayermx),pdv(ngridmx,nlayermx)
30      REAL, INTENT(IN) :: pdq(ngridmx,nlayermx,nqmx),pdt(ngridmx,nlayermx)
31      REAL, INTENT(IN) :: q2(ngridmx,nlayermx+1)
32      REAL, INTENT(IN) :: long(ngridmx),lati(ngridmx)
33      REAL, INTENT(IN) :: zpopsk(ngridmx,nlayermx)
34
35!--------------------------------------------------------
36! Variables de sortie (ou entree/sortie)
37!--------------------------------------------------------
38
39      REAL pdu_th(ngridmx,nlayermx),pdv_th(ngridmx,nlayermx)
40      REAL pdt_th(ngridmx,nlayermx),pdq_th(ngridmx,nlayermx,nqmx)
41      INTEGER lmax_th(ngridmx)
42      REAL zmax_th(ngridmx)
43      REAL pbl_dtke(ngridmx,nlayermx+1)
44
45!--------------------------------------------------------
46! Variables du thermique
47!--------------------------------------------------------
48      REAL u_seri(ngridmx,nlayermx), v_seri(ngridmx,nlayermx)
49      REAL t_seri(ngridmx,nlayermx)
50      REAL d_t_ajs(ngridmx,nlayermx)
51      REAL d_u_ajs(ngridmx,nlayermx), d_q_ajs(ngridmx,nlayermx,nqmx)
52      REAL d_v_ajs(ngridmx,nlayermx)
53      REAL fm_therm(ngridmx,nlayermx+1), entr_therm(ngridmx,nlayermx)
54      REAL detr_therm(ngridmx,nlayermx)
55      REAL zw2(ngridmx,nlayermx+1)
56      REAL fraca(ngridmx,nlayermx+1)
57      REAL ztla(ngridmx,nlayermx)
58      REAL q_therm(ngridmx,nlayermx), pq_therm(ngridmx,nlayermx,nqmx)
59      REAL dq_therm(ngridmx,nlayermx), dq_thermdown(ngridmx,nlayermx)
60      REAL q2_therm(ngridmx,nlayermx), dq2_therm(ngridmx,nlayermx)
61
62      LOGICAL qtransport_thermals,dtke_thermals
63
64      INTEGER l,ig,iq
65
66! Variable de diagnostique : flux de chaleur vertical
67
68      REAL heatFlux(ngridmx,nlayermx)
69      REAL heatFlux_down(ngridmx,nlayermx)
70      REAL buoyancyOut(ngridmx,nlayermx)
71      REAL buoyancyEst(ngridmx,nlayermx)
72      REAL hfmax(ngridmx),wmax(ngridmx)
73
74!---------------------------------------------------------
75!---------------------------------------------------------
76! **********************************************************************
77! Thermique
78! **********************************************************************
79
80! Initialisation des sorties
81
82      lmax_th(:)=1
83      pdu_th(:,:)=0.
84      pdv_th(:,:)=0.
85      pdt_th(:,:)=0.
86      entr_therm(:,:)=0.
87      detr_therm(:,:)=0.
88      q2_therm(:,:)=0.
89      dq2_therm(:,:)=0.
90      dq_therm(:,:)=0.
91      dq_thermdown(:,:)=0.
92      ztla(:,:)=0.
93      pbl_dtke(:,:)=0.
94      fm_therm(:,:)=0.
95      zw2(:,:)=0.
96      fraca(:,:)=0.
97      if (tracer) then
98         pdq_th(:,:,:)=0.
99      end if
100
101! Dans le model terrestres, les seri sont des q+dq tendances déja cumulées. Il n'y a donc pas de
102! cumulage à l'intérieur de la routine comme dans le model martien. On le fait ici :
103
104            u_seri(:,:)=pu(:,:)+pdu(:,:)*ptimestep
105            v_seri(:,:)=pv(:,:)+pdv(:,:)*ptimestep
106            t_seri(:,:)=pt(:,:)+pdt(:,:)*ptimestep
107
108            pq_therm(:,:,:)=0.
109            qtransport_thermals=.true.
110            call getin("qtransport_thermals",qtransport_thermals)
111            if(qtransport_thermals) then
112            if(tracer) then
113            pq_therm(:,:,:)=pq(:,:,:)+pdq(:,:,:)*ptimestep
114            endif
115            endif
116
117            d_t_ajs(:,:)=0.
118            d_u_ajs(:,:)=0.
119            d_v_ajs(:,:)=0.
120            d_q_ajs(:,:,:)=0.
121            heatFlux(:,:)=0.
122            heatFlux_down(:,:)=0.
123            buoyancyOut(:,:)=0.
124            buoyancyEst(:,:)=0.
125
126       dtke_thermals=.false.
127       call getin("dtke_thermals",dtke_thermals)
128         if(dtke_thermals) then
129
130         DO l=1,nlayermx
131              q2_therm(:,l)=0.5*(q2(:,l)+q2(:,l+1))
132         ENDDO
133         endif
134
135         CALL calltherm_mars(ptimestep,zzlev,zzlay &
136     &      ,pplay,pplev,pphi &
137     &      ,u_seri,v_seri,t_seri,pq_therm, q2_therm &
138     &      ,d_u_ajs,d_v_ajs,d_t_ajs,d_q_ajs, dq2_therm &
139     &      ,fm_therm,entr_therm,detr_therm &
140     &      ,lmax_th,zmax_th &
141     &      ,zw2,fraca &
142     &      ,zpopsk,ztla,heatFlux,heatFlux_down &
143     &      ,buoyancyOut,buoyancyEst,hfmax,wmax)
144
145! Accumulation des  tendances. On n'accumule pas les quantités de traceurs car celle ci n'a pas du changer
146! étant donné qu'on ne prends en compte que q_seri de la vap d'eau = 0
147
148! INCREMENTATION : les d_u_ sont des tendances alors que les pdu sont des dérivees, attention !
149
150           pdu_th(:,:)=d_u_ajs(:,:)/ptimestep
151           pdv_th(:,:)=d_v_ajs(:,:)/ptimestep
152           pdt_th(:,:)=d_t_ajs(:,:)/ptimestep
153           if(qtransport_thermals) then
154           if(tracer) then
155           pdq_th(:,:,:)=d_q_ajs(:,:,:)/ptimestep
156           endif
157           endif
158
159
160         DO l=2,nlayermx
161              pbl_dtke(:,l)=0.5*(dq2_therm(:,l-1)+dq2_therm(:,l))/ptimestep
162         ENDDO
163
164         pbl_dtke(:,1)=0.5*dq2_therm(:,1)/ptimestep
165         pbl_dtke(:,nlayermx+1)=0.
166!! DIAGNOSTICS
167       
168        if(outptherm) then
169        if (ngridmx .eq. 1) then
170        call WRITEDIAGFI(ngridmx,'entr_therm','entrainement thermique',&
171     &                       'kg/m-2',1,entr_therm)
172        call WRITEDIAGFI(ngridmx,'detr_therm','detrainement thermique',&
173     &                       'kg/m-2',1,detr_therm)
174        call WRITEDIAGFI(ngridmx,'fm_therm','flux masse thermique',&
175     &                       'kg/m-2',1,fm_therm)
176        call WRITEDIAGFI(ngridmx,'zw2','vitesse verticale thermique',&
177     &                       'm/s',1,zw2)
178        call WRITEDIAGFI(ngridmx,'heatFlux_up','heatFlux_updraft',&
179     &                       'SI',1,heatFlux)
180       call WRITEDIAGFI(ngridmx,'heatFlux_down','heatFlux_downdraft',&
181     &                       'SI',1,heatFlux_down)
182        call WRITEDIAGFI(ngridmx,'fraca','fraction coverage',&
183     &                       'percent',1,fraca)
184        call WRITEDIAGFI(ngridmx,'buoyancyOut','buoyancyOut',&
185     &                       'm.s-2',1,buoyancyOut)
186        call WRITEDIAGFI(ngridmx,'buoyancyEst','buoyancyEst',&
187     &                       'm.s-2',1,buoyancyEst)
188        call WRITEDIAGFI(ngridmx,'d_t_th',  &
189     &         'tendance temp TH','K',1,d_t_ajs)
190        call WRITEDIAGFI(ngridmx,'zmax',  &
191     &         'pbl height','m',0,zmax_th)
192      else
193
194        call WRITEDIAGFI(ngridmx,'entr_therm','entrainement thermique',&
195     &                       'kg/m-2',3,entr_therm)
196        call WRITEDIAGFI(ngridmx,'detr_therm','detrainement thermique',&
197     &                       'kg/m-2',3,detr_therm)
198        call WRITEDIAGFI(ngridmx,'fm_therm','flux masse thermique',&
199     &                       'kg/m-2',3,fm_therm)
200        call WRITEDIAGFI(ngridmx,'zw2','vitesse verticale thermique',&
201     &                       'm/s',3,zw2)
202        call WRITEDIAGFI(ngridmx,'heatFlux','heatFlux',&
203     &                       'SI',3,heatFlux)
204        call WRITEDIAGFI(ngridmx,'buoyancyOut','buoyancyOut',&
205     &                       'SI',3,buoyancyOut)
206        call WRITEDIAGFI(ngridmx,'d_t_th',  &
207     &         'tendance temp TH','K',3,d_t_ajs)
208
209      endif
210      endif
211
212       END
Note: See TracBrowser for help on using the repository browser.