source: trunk/LMDZ.PLUTO.old/libf/phypluto/convadj.F @ 3436

Last change on this file since 3436 was 3175, checked in by emillour, 11 months ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

File size: 9.7 KB
Line 
1      SUBROUTINE convadj(ngrid,nlay,nq,ptimestep,
2     S                   pplay,pplev,ppopsk,
3     $                   pu,pv,ph,pq,
4     $                   pdufi,pdvfi,pdhfi,pdqfi,
5     $                   pduadj,pdvadj,pdhadj,
6     $                   pdqadj)
7      IMPLICIT NONE
8
9c=======================================================================
10c
11c   ajustement convectif sec
12c   on ajoute les tendances pdhfi au profil pdh avant l'ajustement
13c   SPECIAL VERSION : if one tracer is N2, take into account the
14c   Molecular mass variation (e.g. when N2 condense) to trigger
15c   convection  F. Forget 01/2005
16c
17c=======================================================================
18
19c-----------------------------------------------------------------------
20c   declarations:
21c   -------------
22
23#include "dimensions.h"
24#include "dimphys.h"
25#include "comcstfi.h"
26#include "callkeys.h"
27#include "tracer.h"
28
29
30c   arguments:
31c   ----------
32
33      INTEGER ngrid,nlay
34      REAL ptimestep
35      REAL ph(ngrid,nlay),pdhfi(ngrid,nlay),pdhadj(ngrid,nlay)
36      REAL pplay(ngrid,nlay),pplev(ngrid,nlay+1),ppopsk(ngrid,nlay)
37      REAL pu(ngrid,nlay),pdufi(ngrid,nlay),pduadj(ngrid,nlay)
38      REAL pv(ngrid,nlay),pdvfi(ngrid,nlay),pdvadj(ngrid,nlay)
39
40c    Traceurs :
41      integer nq
42      real pq(ngrid,nlay,nq), pdqfi(ngrid,nlay,nq)
43      real pdqadj(ngrid,nlay,nq)
44
45
46c   local:
47c   ------
48
49      INTEGER ig,i,l,l1,l2,jj
50      INTEGER jcnt, jadrs(ngridmx)
51
52      REAL sig(nlayermx+1),sdsig(nlayermx),dsig(nlayermx)
53      REAL zu(ngridmx,nlayermx),zv(ngridmx,nlayermx)
54      REAL zh(ngridmx,nlayermx)
55      REAL zu2(ngridmx,nlayermx),zv2(ngridmx,nlayermx)
56      REAL zh2(ngridmx,nlayermx), zhc(ngridmx,nlayermx)
57      REAL zhm,zsm,zdsm,zum,zvm,zalpha,zhmc
58     
59
60c    Traceurs :
61      INTEGER iq,in2
62      save in2
63      REAL zq(ngridmx,nlayermx,nqmx), zq2(ngridmx,nlayermx,nqmx)
64      REAL zqm(nqmx),zqn2m
65      real m_n2, m_non2, A , B
66      save A, B
67c    Temporaire (for diagnostic)
68c      REAL diag_alpha(ngridmx)
69
70      real mtot1, mtot2 , mm1, mm2
71       integer l1ref, l2ref
72      LOGICAL vtest(ngridmx),down,firstcall
73      save firstcall
74      data firstcall/.true./
75
76      EXTERNAL SCOPY
77c
78c-----------------------------------------------------------------------
79c   initialisation:
80c   ---------------
81c
82      IF (firstcall) THEN
83        IF(ngrid.NE.ngridmx) THEN
84           PRINT*
85           PRINT*,'STOP dans convadj'
86           PRINT*,'ngrid    =',ngrid
87           PRINT*,'ngridmx  =',ngridmx
88        ENDIF
89        in2=0
90        if (tracer) then
91c          Prepare Special treatment if one of the tracer is N2 gas
92           do iq=1,nqmx
93             if (noms(iq).eq."n2") then
94c                print*,'dont go there'
95c                stop
96                in2=iq  ! temporaire : no density convection if commented
97                m_n2 = 28.00E-3  ! N2 molecular mass (kg/mol)   
98                m_non2 = 16.00-3  ! Methane ? (kg/mol) 
99c                m_non2 = 33.37E-3  ! Non condensible mol mass (kg/mol)   
100c               Compute A and B coefficient use to compute
101c               mean molecular mass Mair defined by
102c               1/Mair = q(ico2)/m_co2 + (1-q(ico2))/m_noco2
103c               1/Mair = A*q(ico2) + B
104                A =(1/m_n2 - 1/m_non2)
105                B=1/m_non2
106             end if
107           enddo
108        endif
109        firstcall=.false.
110      ENDIF ! of IF (firstcall)
111
112c
113c-----------------------------------------------------------------------
114c   detection des profils a modifier:
115c   ---------------------------------
116c   si le profil est a modifier
117c   (i.e. ph(niv_sup) < ph(niv_inf) )
118c   alors le tableau "vtest" est mis a .TRUE. ;
119c   sinon, il reste a sa valeur initiale (.FALSE.)
120c   cette operation est vectorisable
121c   On en profite pour copier la valeur initiale de "ph"
122c   dans le champ de travail "zh"
123
124
125      DO l=1,nlay
126         DO ig=1,ngrid
127            zh(ig,l)=ph(ig,l)+pdhfi(ig,l)*ptimestep
128            zu(ig,l)=pu(ig,l)+pdufi(ig,l)*ptimestep
129            zv(ig,l)=pv(ig,l)+pdvfi(ig,l)*ptimestep
130         ENDDO
131      ENDDO
132
133      if(tracer) then     
134        DO iq =1, nq
135         DO l=1,nlay
136           DO ig=1,ngrid
137              zq(ig,l,iq)=pq(ig,l,iq)+pdqfi(ig,l,iq)*ptimestep
138           ENDDO
139         ENDDO
140        ENDDO
141      end if
142
143
144      CALL scopy(ngrid*nlay,zh,1,zh2,1)
145      CALL scopy(ngrid*nlay,zu,1,zu2,1)
146      CALL scopy(ngrid*nlay,zv,1,zv2,1)
147      CALL scopy(ngrid*nlay*nq,zq,1,zq2,1)
148
149      DO ig=1,ngrid
150        vtest(ig)=.FALSE.
151      ENDDO
152c
153      if (in2.ne.0) then
154c        Special case if one of the tracer is N2 gas
155         DO l=1,nlay
156           DO ig=1,ngrid
157             zhc(ig,l) = zh2(ig,l)*(A*zq2(ig,l,in2)+B)
158           ENDDO
159         ENDDO
160       else
161          CALL scopy(ngrid*nlay,zh2,1,zhc,1)
162       end if
163
164       
165
166      DO l=2,nlay
167        DO ig=1,ngrid
168          IF(zhc(ig,l).LT.zhc(ig,l-1)) vtest(ig)=.TRUE.
169        ENDDO
170      ENDDO
171c
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
181c-----------------------------------------------------------------------
182c  Ajustement des "jcnt" profils instables indices par "jadrs":
183c  ------------------------------------------------------------
184c
185      DO jj = 1, jcnt   ! loop on every convective grid point
186c
187          i = jadrs(jj)
188 
189c   Calcul des niveaux sigma sur cette colonne
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
199c
200c      -- boucle de sondage vers le haut
201c
202cins$     Loop  vers le haut sur l2
203          DO
204c
205            l2 = l2 + 1
206            IF (l2 .GT. nlay) EXIT
207            IF (zhc(i, l2) .LT. zhc(i, l2-1)) THEN
208 
209c          -- l2 est le niveau le plus haut de la colonne instable
210 
211              l1 = l2 - 1
212              l  = l1
213              zsm = sdsig(l2)
214              zdsm = dsig(l2)
215              zhm = zh2(i, l2)
216              if(in2.ne.0) zqn2m = zq2(i,l2,in2)
217c
218c          -- boucle de sondage vers le bas
219c             Loop
220              DO
221c
222                zsm = zsm + sdsig(l)
223                zdsm = zdsm + dsig(l)
224                zhm = zhm + sdsig(l) * (zh2(i, l) - zhm) / zsm
225                if(in2.ne.0) then
226                  zqn2m =
227     &            zqn2m + dsig(l) * (zq2(i,l,in2) - zqn2m) / zdsm
228                  zhmc = zhm*(A*zqn2m+B)
229                else
230                  zhmc = zhm
231                end if
232 
233c            -- doit on etendre la colonne vers le bas ?
234 
235                down = .FALSE.
236                IF (l1 .NE. 1) THEN    !--  and then
237                  IF (zhmc .LT. zhc(i, l1-1)) THEN
238                    down = .TRUE.
239                  END IF
240                END IF
241 
242                IF (down) THEN
243 
244                  l1 = l1 - 1
245                  l  = l1
246 
247                ELSE
248 
249c              -- peut on etendre la colonne vers le haut ?
250 
251                  IF (l2 .EQ. nlay) EXIT
252 
253                  IF (zhc(i, l2+1) .GE. zhmc) EXIT
254c
255                  l2 = l2 + 1
256                  l  = l2
257c
258                END IF
259c
260cins$         End Loop
261              ENDDO
262c
263c          -- nouveau profil : constant (valeur moyenne)
264c
265              zalpha=0.
266              zum=0.
267              zvm=0.
268              do iq=1,nq
269                zqm(iq) = 0.
270              end do
271              DO l = l1, l2
272                if(in2.ne.0) then
273                  zalpha=zalpha+
274     &            ABS(zhc(i,l)/(A+B*zqn2m) -zhm)*dsig(l)
275                else
276                  zalpha=zalpha+ABS(zh2(i,l)-zhm)*dsig(l)
277                endif
278                zh2(i, l) = zhm
279                zum=zum+dsig(l)*zu(i,l)
280                zvm=zvm+dsig(l)*zv(i,l)
281                do iq=1,nq
282                   zqm(iq) = zqm(iq)+dsig(l)*zq(i,l,iq)
283                end do
284              ENDDO
285              zalpha=zalpha/(zhm*(sig(l1)-sig(l2+1)))
286              zum=zum/(sig(l1)-sig(l2+1))
287              zvm=zvm/(sig(l1)-sig(l2+1))
288              do iq=1,nq
289                 zqm(iq) = zqm(iq)/(sig(l1)-sig(l2+1))
290              end do
291
292              IF(zalpha.GT.1.) THEN
293                 zalpha=1.
294              ELSE
295c                IF(zalpha.LT.0.) STOP
296                 IF(zalpha.LT.1.e-4) zalpha=1.e-4
297              ENDIF
298
299              DO l=l1,l2
300                 zu2(i,l)=zu2(i,l)+zalpha*(zum-zu2(i,l))
301                 zv2(i,l)=zv2(i,l)+zalpha*(zvm-zv2(i,l))
302                 do iq=1,nq
303c                  zq2(i,l,iq)=zq2(i,l,iq)+zalpha*(zqm(iq)-zq2(i,l,iq))
304                   zq2(i,l,iq)=zqm(iq)
305                 end do
306              ENDDO
307c              diag_alpha(i)=zalpha  !temporaire
308              if (in2.ne.0) then
309                DO l=l1, l2
310                  zhc(i,l) = zh2(i,l)*(A*zq2(i,l,in2)+B)
311                ENDDO
312              end if
313
314 
315              l2 = l2 + 1
316c
317            END IF   ! fin traitement instabilité entre l1 et l2.
318c                      On repart pour test à partir du l2 au dessus...
319          ENDDO   ! End Loop sur l2 vers le haut
320c
321      ENDDO
322c
323      DO l=1,nlay
324        DO ig=1,ngrid
325          pdhadj(ig,l)=(zh2(ig,l)-zh(ig,l))/ptimestep
326          pduadj(ig,l)=(zu2(ig,l)-zu(ig,l))/ptimestep
327          pdvadj(ig,l)=(zv2(ig,l)-zv(ig,l))/ptimestep
328        ENDDO
329      ENDDO
330
331      if(tracer) then
332        do iq=1, nq
333          do  l=1,nlay
334            do ig=1, ngrid
335              pdqadj(ig,l,iq)=(zq2(ig,l,iq)-zq(ig,l,iq))/ptimestep
336            end do
337          end do
338        end do
339      end if
340
341c     output
342!      if (ngrid.eq.1) then
343!         ig=1
344!         iq =1
345!         write(*,*)'**** l, pq(ig,l,iq),zq(ig,l,iq),zq2(ig,l,iq)' 
346!         do l=nlay,1,-1
347!           write(*,*) l, pq(ig,l,iq),zq(ig,l,iq),zq2(ig,l,iq)
348!         end do
349!      end if
350
351
352      RETURN
353      END
Note: See TracBrowser for help on using the repository browser.