source: trunk/LMDZ.MARS/libf/phymars/convadj.F @ 1009

Last change on this file since 1009 was 161, checked in by acolaitis, 13 years ago

================================================
======== IMPLEMENTATION OF THERMALS ============
================================================

Author: A. Colaitis (2011-06-16)

The main goal of this revision is to start including the thermals into the model
for development purposes. Users should not use the thermals yet, as
several major configuration changes still need to be done.

This version includes :

  • updraft and downdraft parametrizations
  • velocity in the thermal, including drag
  • plume height analysis
  • closure equation
  • updraft transport of heat, tracers and momentum
  • downdraft transport of heat

This model should not be used without upcoming developments, namely :

  • downdraft transport of tracers and momentum
  • updraft & downdraft transport of q2 (tke)
  • revision of vdif_kc to compute q2 for non-stratified cases

Thermals could also include in a later revision :

  • momentum loss during transport (horizontal drag)

Compilation of the thermals has been successfully tested on ifort, gfortran and pgf90

================================================
================================================

M libf/phymars/callkeys.h
M libf/phymars/inifis.F

Added new control flags to call the thermals :

  • calltherm (false by default) <- to call thermals
  • outptherm (false by default) <- to output thermal-related diagnostics (for dev purposes)

================================================

M libf/phymars/vdifc.F
------> added a temporary output for thermal-related diagnostics

M libf/phymars/testphys1d.F
------> added treatment for a initialization from a profile of neutral gas (ar)

-> will be transformed in a decaying tracer for thermal diagnostics

M libf/phymars/physiq.F
------> added a section to call the thermals

-> changed the call to convadj
-> added thermal-related outputs for diagnostics

M libf/phymars/convadj.F
------> takes now into account the height of thermals to execute convective adjustment

=> note : convective adjustment needs to be activated when using thermals, in case of a

second instable layer above the thermals

================================================

A libf/phymars/calltherm_interface.F90
------> Interface between physiq.F and the thermals

A libf/phymars/calltherm_mars.F90
------> Routine running the sub-timestep of the thermals

A libf/phymars/thermcell_main_mars.F90
------> Main thermals routine specific to Martian physics

A libf/phymars/thermcell_dqupdown.F90
------> Thermals subroutine computing transport of quantities by updrafts and downdrafts

A libf/phymars/thermcell.F90
------> Module including parameters from the Earth to Mars importation. Will disappear in future dev

================================================
================================================

File size: 11.8 KB
RevLine 
[38]1      subroutine convadj(ngrid,nlay,nq,ptimestep,
[161]2     &                   pplay,pplev,ppopsk,lmax_th,
[38]3     &                   pu,pv,ph,pq,
4     &                   pdufi,pdvfi,pdhfi,pdqfi,
5     &                   pduadj,pdvadj,pdhadj,
6     &                   pdqadj)
7
8      implicit none
9
10!==================================================================
11!     
12!     Purpose
13!     -------
14!     Calculates dry convective adjustment. If one tracer is CO2,
15!     we take into account the molecular mass variation (e.g. when
16!     CO2 condenses) to trigger convection (F. Forget 01/2005)
17!
18!     Authors
19!     -------
20!     Original author unknown.
21!     Modif. 2005 by F. Forget.
22!     Modif. 2010 by R. Wordsworth
[161]23!     Modif. 2011 by A. Colaitis
24!
[38]25!==================================================================
26
27!     ------------
28!     Declarations
29!     ------------
30
31#include "dimensions.h"
32#include "dimphys.h"
33#include "comcstfi.h"
34#include "callkeys.h"
35#include "tracer.h"
36
37
38!     Arguments
39!     ---------
40
[161]41      INTEGER,intent(in) :: ngrid,nlay,lmax_th(ngrid)
[38]42      REAL,intent(in) :: ptimestep
43      REAL,intent(in) :: ph(ngrid,nlay)
44      REAL,intent(in) :: pdhfi(ngrid,nlay)
45      REAL,intent(out) :: pdhadj(ngrid,nlay)
46      REAL,intent(in) :: pplay(ngrid,nlay),pplev(ngrid,nlay+1)
47      REAL,intent(in) :: ppopsk(ngrid,nlay)
48      REAL,intent(in) :: pu(ngrid,nlay),pdufi(ngrid,nlay)
49      REAL,intent(out) :: pduadj(ngrid,nlay)
50      REAL,intent(in) :: pv(ngrid,nlay),pdvfi(ngrid,nlay)
51      REAL,intent(out) :: pdvadj(ngrid,nlay)
52
53!     Tracers
54      integer,intent(in) :: nq
55      real,intent(in) :: pq(ngrid,nlay,nq), pdqfi(ngrid,nlay,nq)
56      real,intent(out) :: pdqadj(ngrid,nlay,nq)
57
58
59!     Local
60!     -----
61
62      INTEGER ig,i,l,l1,l2,jj
63      INTEGER jcnt, jadrs(ngridmx)
64
65      REAL sig(nlayermx+1),sdsig(nlayermx),dsig(nlayermx)
66      REAL zu(ngridmx,nlayermx),zv(ngridmx,nlayermx)
67      REAL zh(ngridmx,nlayermx)
68      REAL zu2(ngridmx,nlayermx),zv2(ngridmx,nlayermx)
69      REAL zh2(ngridmx,nlayermx), zhc(ngridmx,nlayermx)
70      REAL zhm,zsm,zdsm,zum,zvm,zalpha,zhmc
71
72!     Tracers
73      INTEGER iq,ico2
74      save ico2
75      REAL zq(ngridmx,nlayermx,nqmx), zq2(ngridmx,nlayermx,nqmx)
76      REAL zqm(nqmx),zqco2m
77      real m_co2, m_noco2, A , B
78      save A, B
79
80      real mtot1, mtot2 , mm1, mm2
81       integer l1ref, l2ref
82      LOGICAL vtest(ngridmx),down,firstcall
83      save firstcall
84      data firstcall/.true./
85
86!     for conservation test
87      real masse,cadjncons
88
89!     --------------
90!     Initialisation
91!     --------------
92
93      IF (firstcall) THEN
94        IF(ngrid.NE.ngridmx) THEN
95           PRINT*
96           PRINT*,'STOP in convadj'
97           PRINT*,'ngrid    =',ngrid
98           PRINT*,'ngridmx  =',ngridmx
99        ENDIF
100        ico2=0
101        if (tracer) then
102!     Prepare Special treatment if one of the tracers is CO2 gas
103           do iq=1,nqmx
104             if (noms(iq).eq."co2") then
105                ico2=iq
106                m_co2 = 44.01E-3  ! CO2 molecular mass (kg/mol)   
107                m_noco2 = 33.37E-3  ! Non condensible mol mass (kg/mol)   
108!               Compute A and B coefficient use to compute
109!               mean molecular mass Mair defined by
110!               1/Mair = q(ico2)/m_co2 + (1-q(ico2))/m_noco2
111!               1/Mair = A*q(ico2) + B
112                A =(1/m_co2 - 1/m_noco2)
113                B=1/m_noco2
114             end if
115           enddo
116        endif
117        firstcall=.false.
118      ENDIF ! of IF (firstcall)
119
120      DO l=1,nlay
121         DO ig=1,ngrid
122            zh(ig,l)=ph(ig,l)+pdhfi(ig,l)*ptimestep
123            zu(ig,l)=pu(ig,l)+pdufi(ig,l)*ptimestep
124            zv(ig,l)=pv(ig,l)+pdvfi(ig,l)*ptimestep
125         ENDDO
126      ENDDO
127
128      if(tracer) then     
129        DO iq =1, nq
130         DO l=1,nlay
131           DO ig=1,ngrid
132              zq(ig,l,iq)=pq(ig,l,iq)+pdqfi(ig,l,iq)*ptimestep
133           ENDDO
134         ENDDO
135        ENDDO
136      end if
137
138      zh2(:,:)=zh(:,:)
139      zu2(:,:)=zu(:,:)
140      zv2(:,:)=zv(:,:)
141      zq2(:,:,:)=zq(:,:,:)
142
143!     -----------------------------
144!     Detection of unstable columns
145!     -----------------------------
146!     If ph(above) < ph(below) we set vtest=.true.
147
148      DO ig=1,ngrid
149        vtest(ig)=.false.
150      ENDDO
151
152      if (ico2.ne.0) then
153!     Special case if one of the tracers is CO2 gas
154         DO l=1,nlay
155           DO ig=1,ngrid
156             zhc(ig,l) = zh2(ig,l)*(A*zq2(ig,l,ico2)+B)
157           ENDDO
158         ENDDO
159       else
160          zhc(:,:)=zh2(:,:)
161       end if
162
163!     Find out which grid points are convectively unstable
164      DO l=2,nlay
165        DO ig=1,ngrid
[161]166          IF((zhc(ig,l).LT.zhc(ig,l-1))                                 $
167     $  .AND. (l .GT. lmax_th(ig))) vtest(ig)=.true.
168       ENDDO
[38]169      ENDDO
170
171!     Make a list of them
172      jcnt=0
173      DO ig=1,ngrid
174         IF(vtest(ig)) THEN
175            jcnt=jcnt+1
176            jadrs(jcnt)=ig
177         ENDIF
178      ENDDO
179
180
181!     ---------------------------------------------------------------
182!     Adjustment of the "jcnt" unstable profiles indicated by "jadrs"
183!     ---------------------------------------------------------------
184
185      DO jj = 1, jcnt   ! loop on every convective grid point
186
187          i = jadrs(jj)
188 
189!     Calculate sigma in this column
190          DO l=1,nlay+1
191            sig(l)=pplev(i,l)/pplev(i,1)
192       
193          ENDDO
194         DO l=1,nlay
195            dsig(l)=sig(l)-sig(l+1)
196            sdsig(l)=ppopsk(i,l)*dsig(l)
197         ENDDO
198          l2 = 1
199
200!     Test loop upwards on l2
201
[161]202      DO
203       l2 = l2 + 1
204       IF (l2 .GT. nlay) EXIT
205       IF ((zhc(i, l2) .LT. zhc(i, l2-1)).AND.(l2 .GT. lmax_th(i))) THEN
206
[38]207!     l2 is the highest level of the unstable column
208 
209              l1 = l2 - 1
210              l  = l1
211              zsm = sdsig(l2)
212              zdsm = dsig(l2)
213              zhm = zh2(i, l2)
214              if(ico2.ne.0) zqco2m = zq2(i,l2,ico2)
215
216!     Test loop downwards
217
218              DO
219                zsm = zsm + sdsig(l)
220                zdsm = zdsm + dsig(l)
221                zhm = zhm + sdsig(l) * (zh2(i, l) - zhm) / zsm
222                if(ico2.ne.0) then
223                  zqco2m =
224     &            zqco2m + dsig(l) * (zq2(i,l,ico2) - zqco2m) / zdsm
225                  zhmc = zhm*(A*zqco2m+B)
226                else
227                  zhmc = zhm
228                end if
229 
230!     do we have to extend the column downwards?
231 
[161]232            down = .false.
233            IF (l1 .ne. 1) then    !--  and then
234              IF ((zhmc .lt. zhc(i, l1-1)).and.(l1.gt.lmax_th(i))) then
235                down = .true.
236              END IF
237            END IF
[38]238 
239                ! this could be a problem...
240
241                if (down) then
242 
243                  l1 = l1 - 1
244                  l  = l1
245 
246                else
247 
248!     can we extend the column upwards?
249 
250                  if (l2 .eq. nlay) exit
251 
252                  if (zhc(i, l2+1) .ge. zhmc) exit
253
254                  l2 = l2 + 1
255                  l  = l2
256
257                end if ! of if (down)
258
259              enddo ! of do ! Test loop forward
260
261!     New constant profile (average value)
262
263
264              zalpha=0.
265              zum=0.
266              zvm=0.
267              do iq=1,nq
268                zqm(iq) = 0.
269              end do
270              DO l = l1, l2
271                if(ico2.ne.0) then
272                  zalpha=zalpha+
273     &            ABS(zhc(i,l)/(A+B*zqco2m) -zhm)*dsig(l)
274                else
275                  zalpha=zalpha+ABS(zh2(i,l)-zhm)*dsig(l)
276                endif
277                zh2(i, l) = zhm
278!     modifs by RDW !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
279                zum=zum+dsig(l)*zu2(i,l)
280                zvm=zvm+dsig(l)*zv2(i,l)
281!                zum=zum+dsig(l)*zu(i,l)
282!                zvm=zvm+dsig(l)*zv(i,l)
283                do iq=1,nq
284                   zqm(iq) = zqm(iq)+dsig(l)*zq2(i,l,iq)
285!                   zqm(iq) = zqm(iq)+dsig(l)*zq(i,l,iq)
286!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
287
288!     to conserve tracers/ KE, we must calculate zum, zvm and zqm using
289!     the up-to-date column values. If we do not do this, there are cases
290!     where convection stops at one level and starts at the next where we
291!     can break conservation of stuff (particularly tracers) significantly.
292
293                end do
294              ENDDO ! of DO l = l1, l2
295              zalpha=zalpha/(zhm*(sig(l1)-sig(l2+1)))
296              zum=zum/(sig(l1)-sig(l2+1))
297              zvm=zvm/(sig(l1)-sig(l2+1))
298              do iq=1,nq
299                 zqm(iq) = zqm(iq)/(sig(l1)-sig(l2+1))
300              end do
301
302              IF(zalpha.GT.1.) THEN
303                 zalpha=1.
304              ELSE
305!                IF(zalpha.LT.0.) STOP
306                 IF(zalpha.LT.1.e-4) zalpha=1.e-4
307              ENDIF
308
309              DO l=l1,l2
310                 zu2(i,l)=zu2(i,l)+zalpha*(zum-zu2(i,l))
311                 zv2(i,l)=zv2(i,l)+zalpha*(zvm-zv2(i,l))
312                 do iq=1,nq
313!                  zq2(i,l,iq)=zq2(i,l,iq)+zalpha*(zqm(iq)-zq2(i,l,iq))
314                   zq2(i,l,iq)=zqm(iq)
315                 end do
316              ENDDO
317              if (ico2.ne.0) then
318                DO l=l1, l2
319                  zhc(i,l) = zh2(i,l)*(A*zq2(i,l,ico2)+B)
320                ENDDO
321              end if
322
323
324              l2 = l2 + 1
325
326            END IF   ! End of l1 to l2 instability treatment
327                     ! We now continue to test from l2 upwards
328
329          ENDDO   ! End of upwards loop on l2
330
331
332!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
333!     check conservation
334         cadjncons=0.0
335         if(water)then
336          iq    = igcm_h2o_vap
337          do l = 1, nlay
338            masse = (pplev(i,l) - pplev(i,l+1))/g
339            cadjncons = cadjncons +
340     &           masse*(zq2(i,l,iq)-zq(i,l,iq))/ptimestep
341          end do
342         endif
343
344         if(cadjncons.lt.-1.e-6)then
345            print*,'convadj has just crashed...'
346            print*,'i  = ',i
347            print*,'l1 = ',l1
348            print*,'l2 = ',l2
349            print*,'cadjncons        = ',cadjncons
350         do l = 1, nlay
351            print*,'dsig         = ',dsig(l)
352         end do         
353         do l = 1, nlay
354            print*,'dsig         = ',dsig(l)
355         end do
356         do l = 1, nlay
357            print*,'sig         = ',sig(l)
358         end do
359         do l = 1, nlay
360            print*,'pplay(ig,:)         = ',pplay(i,l)
361         end do
362         do l = 1, nlay+1
363            print*,'pplev(ig,:)         = ',pplev(i,l)
364         end do
365         do l = 1, nlay
366            print*,'ph(ig,:)         = ',ph(i,l)
367         end do
368         do l = 1, nlay
369            print*,'zh(ig,:)         = ',zh(i,l)
370         end do
371         do l = 1, nlay
372            print*,'zh2(ig,:)        = ',zh2(i,l)
373         end do
374         do l = 1, nlay
375            print*,'zq(ig,:,vap)     = ',zq(i,l,igcm_h2o_vap)
376         end do
377         do l = 1, nlay
378            print*,'zq2(ig,:,vap)    = ',zq2(i,l,igcm_h2o_vap)
379         end do
380            print*,'zqm(vap)         = ',zqm(igcm_h2o_vap)
381            print*,'jadrs=',jadrs
382
383            call abort
384         endif
385!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
386
387      ENDDO ! of DO jj = 1, jcnt   ! loop on every convective grid point
388
389
390      DO l=1,nlay
391        DO ig=1,ngrid
392          pdhadj(ig,l)=(zh2(ig,l)-zh(ig,l))/ptimestep
393          pduadj(ig,l)=(zu2(ig,l)-zu(ig,l))/ptimestep
394          pdvadj(ig,l)=(zv2(ig,l)-zv(ig,l))/ptimestep
395        ENDDO
396      ENDDO
397
398      if(tracer) then
399        do iq=1, nq
400          do  l=1,nlay
401            do ig=1, ngrid
402              pdqadj(ig,l,iq)=(zq2(ig,l,iq)-zq(ig,l,iq))/ptimestep
403            end do
404          end do
405        end do
406      end if
407
408
409!     output
410!      if (ngrid.eq.1) then
411!         ig=1
412!         iq =1
413!         write(*,*)'**convadj: l, pq(ig,l,iq),zq(ig,l,iq),zq2(ig,l,iq)' 
414!         do l=nlay,1,-1
415!           write(*,*) l, pq(ig,l,iq),zq(ig,l,iq),zq2(ig,l,iq)
416!         end do
417!      end if
418
419
420      return
421      end
422     
Note: See TracBrowser for help on using the repository browser.