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

Last change on this file since 269 was 268, checked in by acolaitis, 14 years ago

--- AC 03/08/2011 ---
M 267 libf/phymars/physiq.F
<> Minor modification to pass Ch from vdifc to meso_inc_les

M 267 libf/phymars/surflayer_interpol.F
<> Major modification to the formulation of integrals

Now stable for most cases. Some cases with highly negative Monin Obukhov length
remain to be explored.

M 267 libf/phymars/vdif_cd.F
<> Added gustiness to the Richardson computation. Gustiness factor is for now of beta=1., after

several comparisons with LES aerodynamic conductances. May be subject to a minor change (+/- 0.1)
in the near future. (almost transparent for the user)

M 267 libf/phymars/vdifc.F
<> Minor modifications relative to variables.

M 267 libf/phymars/calltherm_mars.F90
<> Added a comment on a "sensitive" parameter that should not be changed without knowing the consequence !

M 267 libf/phymars/meso_inc/meso_inc_les.F
<> Changed the definition for HFX computation in the LES (to be discussed with Aymeric). New definition yields

very similar results to old one and follows a strict definition of what HFX should be.


File size: 6.7 KB
RevLine 
[161]1!
2! $Id: calltherm.F90 1428 2010-09-13 08:43:37Z fairhead $
3!
[185]4      subroutine calltherm_mars(dtime,zzlev,zzlay  &
[161]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  &
[185]8     &      ,fm_therm,entr_therm,detr_therm,lmax,zmax,&
[161]9     &   zw2,fraca,zpopsk,ztla,heatFlux,heatFlux_down,&
[173]10     &     buoyancyOut,buoyancyEst,hfmax,wmax)
[161]11
12       USE ioipsl_getincom
13      implicit none
14
[185]15#include "dimensions.h"
16#include "dimphys.h"
17
[161]18      REAL dtime
[185]19      LOGICAL logexpr0, logexpr2(ngridmx,nlayermx), logexpr1(ngridmx)
[161]20      REAL fact
[185]21      INTEGER nbptspb
[161]22
[185]23      REAL, INTENT(IN) :: zzlay(ngridmx,nlayermx)
24      REAL, INTENT(IN) :: zzlev(ngridmx,nlayermx+1)
[161]25
[185]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)
[161]33!test: on sort lentr et a* pour alimenter KE
[185]34      REAL zw2(ngridmx,nlayermx+1),fraca(ngridmx,nlayermx+1)
35      REAL zzw2(ngridmx,nlayermx+1)
[161]36
37!FH Update Thermiques
[185]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)
[161]43
44!********************************************************
45!     declarations
[185]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)
[161]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
[185]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)
[161]62!
[185]63      integer isplit,nsplit_thermals
64      real r_aspect_thermals
[161]65
[185]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
[161]77      character (len=20) :: modname='calltherm'
78      character (len=80) :: abort_message
79
80      integer i,k
81      logical, save :: first=.true.
82
[185]83      REAL tstart,tstop
84
85
[161]86!  Modele du thermique
87!  ===================
[185]88 
[268]89         r_aspect_thermals=2.   ! 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
[185]94         nsplit_thermals=40
[161]95         call getin("nsplit_thermals",nsplit_thermals)
96
97         fm_therm(:,:)=0.
98         detr_therm(:,:)=0.
99         entr_therm(:,:)=0.
100
101         heatFlux(:,:)=0.
102         heatFlux_down(:,:)=0.
103         buoyancyOut(:,:)=0.
104         buoyancyEst(:,:)=0.
105
106         zw2(:,:)=0.
107
108         zdt=dtime/REAL(nsplit_thermals)
109
110         do isplit=1,nsplit_thermals
111
[185]112!         call cpu_time(tstart)
113
114
[161]115! On reinitialise les flux de masse a zero pour le cumul en
116! cas de splitting
117
118         zfm_therm(:,:)=0.
119         zentr_therm(:,:)=0.
120         zdetr_therm(:,:)=0.
121
122         zheatFlux(:,:)=0.
123         zheatFlux_down(:,:)=0.
124         zbuoyancyOut(:,:)=0.
125         zbuoyancyEst(:,:)=0.
126
127         zzw2(:,:)=0.
128
129         d_t_the(:,:)=0.
130         d_u_the(:,:)=0.
131         d_v_the(:,:)=0.
132         dq2_the(:,:)=0.
[185]133         if (nqmx .ne. 0) then
[161]134            d_q_the(:,:,:)=0.
135         endif
136
[185]137             CALL thermcell_main_mars(zdt  &
[161]138     &      ,pplay,paprs,pphi,zzlev,zzlay  &
139     &      ,u_seri,v_seri,t_seri,pq_therm,q2_therm  &
140     &      ,d_u_the,d_v_the,d_t_the,d_q_the,dq2_the  &
[185]141     &      ,zfm_therm,zentr_therm,zdetr_therm,lmax,zmax  &
[161]142     &      ,r_aspect_thermals &
143     &      ,zzw2,fraca,zpopsk &
144     &      ,ztla,zheatFlux,zheatFlux_down &
145     &      ,zbuoyancyOut,zbuoyancyEst)
146
147      fact=1./REAL(nsplit_thermals)
148!  transformation de la derivee en tendance
149
150            d_t_the(:,:)=d_t_the(:,:)*dtime*fact
151            d_u_the(:,:)=d_u_the(:,:)*fact
152            d_v_the(:,:)=d_v_the(:,:)*fact
153            dq2_the(:,:)=dq2_the(:,:)*fact           
154
[185]155            if (nqmx .ne. 0) then
[161]156               d_q_the(:,:,:)=d_q_the(:,:,:)*fact
157            endif
158
159            fm_therm(:,:)=fm_therm(:,:)  &
160     &      +zfm_therm(:,:)*fact
161            entr_therm(:,:)=entr_therm(:,:)  &
162     &       +zentr_therm(:,:)*fact
163            detr_therm(:,:)=detr_therm(:,:)  &
164     &       +zdetr_therm(:,:)*fact
165
166            heatFlux(:,:)=heatFlux(:,:) &
167     &       +zheatFlux(:,:)*fact
168            heatFlux_down(:,:)=heatFlux_down(:,:) &
[173]169     &       +zheatFlux_down(:,:)*fact
[161]170            buoyancyOut(:,:)=buoyancyOut(:,:) &
171     &       +zbuoyancyOut(:,:)*fact
172            buoyancyEst(:,:)=buoyancyEst(:,:) &
[173]173     &       +zbuoyancyEst(:,:)*fact
[161]174
175            zw2(:,:)=zw2(:,:) + zzw2(:,:)*fact
176
177!  accumulation de la tendance
178     
179            d_t_ajs(:,:)=d_t_ajs(:,:)+d_t_the(:,:)
180            d_u_ajs(:,:)=d_u_ajs(:,:)+d_u_the(:,:)
181            d_v_ajs(:,:)=d_v_ajs(:,:)+d_v_the(:,:)
182            d_q_ajs(:,:,:)=d_q_ajs(:,:,:)+d_q_the(:,:,:)
183            dq2_therm(:,:)=dq2_therm(:,:)+dq2_the(:,:)
184!  incrementation des variables meteo
185     
186            t_seri(:,:) = t_seri(:,:) + d_t_the(:,:)
187            u_seri(:,:) = u_seri(:,:) + d_u_the(:,:)
188            v_seri(:,:) = v_seri(:,:) + d_v_the(:,:)
189            pq_therm(:,:,:) = pq_therm(:,:,:) + d_q_the(:,:,:)
190            q2_therm(:,:) = q2_therm(:,:) + dq2_therm(:,:)
191
[185]192
193!         call cpu_time(tstop)
194!         print*,'elapsed time in thermals : ',tstop-tstart
195
[161]196         enddo ! isplit
197
198     
199!****************************************************************
200
[185]201!          do i=1,ngridmx
202!             do k=1,nlayermx
[161]203!                if (ztla(i,k) .lt. 1.e-10) fraca(i,k) =0.
204!               print*,'youpi je sers a quelque chose !'
205!             enddo
206!          enddo
[173]207       
[185]208          DO i=1,ngridmx
[173]209            hfmax(i)=MAXVAL(heatFlux(i,:)+heatFlux_down(i,:))
210            wmax(i)=MAXVAL(zw2(i,:))
211          ENDDO
212 
[161]213      return
214
215      end
Note: See TracBrowser for help on using the repository browser.