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

Last change on this file since 2311 was 2311, checked in by emillour, 5 years ago

Mars GCM:
Code tidying: use getin_p() instead of getin() and use "call abort_physic"
instead of "stop" or "call abort".
EM

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