source: trunk/LMDZ.GENERIC/libf/phystd/convadj.F @ 2987

Last change on this file since 2987 was 2482, checked in by yjaziri, 4 years ago

Generic GCM:
Clean convadj.F90 specific CO2 Mars convection
Add alb_ocean used in hydrol.F90 as option in .def files
Add kmixmin 1D minimum eddy mix coeff for turbdiff as rcm1d.def option
and comment lines to help coding specific eddy mix coeff in turbdiff with Earth example

YJ

File size: 9.5 KB
Line 
1      subroutine convadj(ngrid,nlay,nq,ptimestep,
2     &                   pplay,pplev,ppopsk,
3     &                   pu,pv,ph,pq,
4     &                   pdufi,pdvfi,pdhfi,pdqfi,
5     &                   pduadj,pdvadj,pdhadj,pdqadj)
6
7      USE tracer_h
8      use comcstfi_mod, only: g
9      use callkeys_mod, only: tracer,water
10
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!     
26!==================================================================
27
28!     ------------
29!     Declarations
30!     ------------
31
32
33!     Arguments
34!     ---------
35
36      INTEGER ngrid,nlay
37      REAL ptimestep
38      REAL ph(ngrid,nlay),pdhfi(ngrid,nlay),pdhadj(ngrid,nlay)
39      REAL pplay(ngrid,nlay),pplev(ngrid,nlay+1),ppopsk(ngrid,nlay)
40      REAL pu(ngrid,nlay),pdufi(ngrid,nlay),pduadj(ngrid,nlay)
41      REAL pv(ngrid,nlay),pdvfi(ngrid,nlay),pdvadj(ngrid,nlay)
42
43!     Tracers
44      integer nq
45      real pq(ngrid,nlay,nq), pdqfi(ngrid,nlay,nq)
46      real pdqadj(ngrid,nlay,nq)
47
48
49!     Local
50!     -----
51
52      INTEGER ig,i,l,l1,l2,jj
53      INTEGER jcnt, jadrs(ngrid)
54
55      REAL sig(nlay+1),sdsig(nlay),dsig(nlay)
56      REAL zu(ngrid,nlay),zv(ngrid,nlay)
57      REAL zh(ngrid,nlay)
58      REAL zu2(ngrid,nlay),zv2(ngrid,nlay)
59      REAL zh2(ngrid,nlay), zhc(ngrid,nlay)
60      REAL zhm,zsm,zdsm,zum,zvm,zalpha,zhmc
61
62!     Tracers
63      INTEGER iq
64      REAL zq(ngrid,nlay,nq), zq2(ngrid,nlay,nq)
65      REAL zqm(nq),zqco2m
66
67      LOGICAL vtest(ngrid),down
68
69!     for conservation test
70      real masse,cadjncons
71
72      EXTERNAL SCOPY
73
74!     --------------
75!     Initialisation
76!     --------------
77
78      DO l=1,nlay
79         DO ig=1,ngrid
80            zh(ig,l)=ph(ig,l)+pdhfi(ig,l)*ptimestep
81            zu(ig,l)=pu(ig,l)+pdufi(ig,l)*ptimestep
82            zv(ig,l)=pv(ig,l)+pdvfi(ig,l)*ptimestep
83         ENDDO
84      ENDDO
85
86      if(tracer) then     
87        DO iq =1, nq
88         DO l=1,nlay
89           DO ig=1,ngrid
90              zq(ig,l,iq)=pq(ig,l,iq)+pdqfi(ig,l,iq)*ptimestep
91           ENDDO
92         ENDDO
93        ENDDO
94      end if
95
96      CALL scopy(ngrid*nlay,zh,1,zh2,1)
97      CALL scopy(ngrid*nlay,zu,1,zu2,1)
98      CALL scopy(ngrid*nlay,zv,1,zv2,1)
99      CALL scopy(ngrid*nlay*nq,zq,1,zq2,1)
100
101!     -----------------------------
102!     Detection of unstable columns
103!     -----------------------------
104!     If ph(above) < ph(below) we set vtest=.true.
105
106      DO ig=1,ngrid
107        vtest(ig)=.false.
108      ENDDO
109
110      CALL scopy(ngrid*nlay,zh2,1,zhc,1)
111
112!     Find out which grid points are convectively unstable
113      DO l=2,nlay
114        DO ig=1,ngrid
115          IF (zhc(ig,l).LT.zhc(ig,l-1)) THEN
116            vtest(ig)=.true.
117          ENDIF
118        ENDDO
119      ENDDO
120     
121!     Make a list of them
122      jcnt=0
123      DO ig=1,ngrid
124         IF(vtest(ig)) THEN
125            jcnt=jcnt+1
126            jadrs(jcnt)=ig
127         ENDIF
128      ENDDO
129
130
131!     ---------------------------------------------------------------
132!     Adjustment of the "jcnt" unstable profiles indicated by "jadrs"
133!     ---------------------------------------------------------------
134
135      DO jj = 1, jcnt   ! loop on every convective grid point
136
137          i = jadrs(jj)
138 
139!     Calculate sigma in this column
140          DO l=1,nlay+1
141            sig(l)=pplev(i,l)/pplev(i,1)
142       
143          ENDDO
144         DO l=1,nlay
145            dsig(l)=sig(l)-sig(l+1)
146            sdsig(l)=ppopsk(i,l)*dsig(l)
147         ENDDO
148          l2 = 1
149
150!     Test loop upwards on l2
151
152          DO
153            l2 = l2 + 1
154            IF (l2 .GT. nlay) EXIT
155            IF (zhc(i, l2).LT.zhc(i, l2-1)) THEN
156 
157!     l2 is the highest level of the unstable column
158 
159              l1 = l2 - 1
160              l  = l1
161              zsm = sdsig(l2)
162              zdsm = dsig(l2)
163              zhm = zh2(i, l2)
164
165!     Test loop downwards
166
167              DO
168                zsm = zsm + sdsig(l)
169                zdsm = zdsm + dsig(l)
170                zhm = zhm + sdsig(l) * (zh2(i, l) - zhm) / zsm
171                zhmc = zhm
172 
173!     do we have to extend the column downwards?
174 
175                down = .false.
176                IF (l1 .ne. 1) then    !--  and then
177                  IF (zhmc.LT.zhc(i, l1-1)) then
178                    down = .true.
179                  END IF
180                END IF
181 
182                ! this could be a problem...
183
184                if (down) then
185 
186                  l1 = l1 - 1
187                  l  = l1
188 
189                else
190 
191!     can we extend the column upwards?
192 
193                  if (l2 .eq. nlay) exit
194 
195                  if (zhc(i, l2+1) .ge. zhmc) exit
196
197                  l2 = l2 + 1
198                  l  = l2
199
200                end if
201
202              enddo
203
204!     New constant profile (average value)
205
206
207              zalpha=0.
208              zum=0.
209              zvm=0.
210              do iq=1,nq
211                zqm(iq) = 0.
212              end do
213              DO l = l1, l2
214                zalpha=zalpha+ABS(zh2(i,l)-zhm)*dsig(l)
215                zh2(i, l) = zhm
216!     modifs by RDW !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
217                zum=zum+dsig(l)*zu2(i,l)
218                zvm=zvm+dsig(l)*zv2(i,l)
219!                zum=zum+dsig(l)*zu(i,l)
220!                zvm=zvm+dsig(l)*zv(i,l)
221                do iq=1,nq
222                   zqm(iq) = zqm(iq)+dsig(l)*zq2(i,l,iq)
223!                   zqm(iq) = zqm(iq)+dsig(l)*zq(i,l,iq)
224!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
225
226!     to conserve tracers/ KE, we must calculate zum, zvm and zqm using
227!     the up-to-date column values. If we do not do this, there are cases
228!     where convection stops at one level and starts at the next where we
229!     can break conservation of stuff (particularly tracers) significantly.
230
231                end do
232              ENDDO
233              zalpha=zalpha/(zhm*(sig(l1)-sig(l2+1)))
234              zum=zum/(sig(l1)-sig(l2+1))
235              zvm=zvm/(sig(l1)-sig(l2+1))
236              do iq=1,nq
237                 zqm(iq) = zqm(iq)/(sig(l1)-sig(l2+1))
238              end do
239
240              IF(zalpha.GT.1.) THEN
241                 zalpha=1.
242              ELSE
243!                IF(zalpha.LT.0.) STOP
244                 IF(zalpha.LT.1.e-4) zalpha=1.e-4
245              ENDIF
246
247              DO l=l1,l2
248                 zu2(i,l)=zu2(i,l)+zalpha*(zum-zu2(i,l))
249                 zv2(i,l)=zv2(i,l)+zalpha*(zvm-zv2(i,l))
250                 do iq=1,nq
251!                  zq2(i,l,iq)=zq2(i,l,iq)+zalpha*(zqm(iq)-zq2(i,l,iq))
252                   zq2(i,l,iq)=zqm(iq)
253                 end do
254              ENDDO
255
256
257              l2 = l2 + 1
258
259            END IF   ! End of l1 to l2 instability treatment
260                     ! We now continue to test from l2 upwards
261
262          ENDDO   ! End of upwards loop on l2
263
264
265!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
266!     check conservation
267         cadjncons=0.0
268         if(water)then
269         do l = 1, nlay
270            masse = (pplev(i,l) - pplev(i,l+1))/g
271            iq    = igcm_h2o_vap
272            cadjncons = cadjncons +
273     &           masse*(zq2(i,l,iq)-zq(i,l,iq))/ptimestep
274         end do
275         endif
276
277         if(cadjncons.lt.-1.e-6)then
278            print*,'convadj has just crashed...'
279            print*,'i  = ',i
280            print*,'l1 = ',l1
281            print*,'l2 = ',l2
282            print*,'cadjncons        = ',cadjncons
283         do l = 1, nlay
284            print*,'dsig         = ',dsig(l)
285         end do         
286         do l = 1, nlay
287            print*,'dsig         = ',dsig(l)
288         end do
289         do l = 1, nlay
290            print*,'sig         = ',sig(l)
291         end do
292         do l = 1, nlay
293            print*,'pplay(ig,:)         = ',pplay(i,l)
294         end do
295         do l = 1, nlay+1
296            print*,'pplev(ig,:)         = ',pplev(i,l)
297         end do
298         do l = 1, nlay
299            print*,'ph(ig,:)         = ',ph(i,l)
300         end do
301         do l = 1, nlay
302            print*,'ph(ig,:)         = ',ph(i,l)
303         end do
304         do l = 1, nlay
305            print*,'ph(ig,:)         = ',ph(i,l)
306         end do
307         do l = 1, nlay
308            print*,'zh(ig,:)         = ',zh(i,l)
309         end do
310         do l = 1, nlay
311            print*,'zh2(ig,:)        = ',zh2(i,l)
312         end do
313         do l = 1, nlay
314            print*,'zq(ig,:,vap)     = ',zq(i,l,igcm_h2o_vap)
315         end do
316         do l = 1, nlay
317            print*,'zq2(ig,:,vap)    = ',zq2(i,l,igcm_h2o_vap)
318         end do
319            print*,'zqm(vap)         = ',zqm(igcm_h2o_vap)
320            print*,'jadrs=',jadrs
321
322            call abort
323         endif
324!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
325
326
327      ENDDO
328
329      DO l=1,nlay
330        DO ig=1,ngrid
331          pdhadj(ig,l)=(zh2(ig,l)-zh(ig,l))/ptimestep
332          pduadj(ig,l)=(zu2(ig,l)-zu(ig,l))/ptimestep
333          pdvadj(ig,l)=(zv2(ig,l)-zv(ig,l))/ptimestep
334        ENDDO
335      ENDDO
336
337      if(tracer) then
338        do iq=1, nq
339          do  l=1,nlay
340            DO ig=1,ngrid
341              pdqadj(ig,l,iq)=(zq2(ig,l,iq)-zq(ig,l,iq))/ptimestep
342            end do
343          end do
344        end do
345      end if
346
347
348!     output
349!      if (ngrid.eq.1) then
350!         ig=1
351!         iq =1
352!         write(*,*)'**** l, pq(ig,l,iq),zq(ig,l,iq),zq2(ig,l,iq)' 
353!         do l=nlay,1,-1
354!           write(*,*) l, pq(ig,l,iq),zq(ig,l,iq),zq2(ig,l,iq)
355!         end do
356!      end if
357
358
359      return
360      end
Note: See TracBrowser for help on using the repository browser.