source: trunk/MESOSCALE/LMDZ.MARS/libf_gcm/phymars/convadj.F @ 1242

Last change on this file since 1242 was 57, checked in by aslmd, 14 years ago

mineur LMD_MM_MARS: ajout du GCM ancienne physique, systeme maintenant complet sur SVN (ne manque que la base de donnees d'etats initiaux)

File size: 9.5 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 CO2, take into account the
14c   Molecular mass variation (e.g. when CO2 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,ico2
62      save ico2
63      REAL zq(ngridmx,nlayermx,nqmx), zq2(ngridmx,nlayermx,nqmx)
64      REAL zqm(nqmx),zqco2m
65      real m_co2, m_noco2, 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        ico2=0
90        if (tracer) then
91c          Prepare Special treatment if one of the tracer is CO2 gas
92           do iq=1,nqmx
93             if (noms(iq).eq."co2") then
94                ico2=iq
95                m_co2 = 44.01E-3  ! CO2 molecular mass (kg/mol)   
96                m_noco2 = 33.37E-3  ! Non condensible mol mass (kg/mol)   
97c               Compute A and B coefficient use to compute
98c               mean molecular mass Mair defined by
99c               1/Mair = q(ico2)/m_co2 + (1-q(ico2))/m_noco2
100c               1/Mair = A*q(ico2) + B
101                A =(1/m_co2 - 1/m_noco2)
102                B=1/m_noco2
103             end if
104           enddo
105           firstcall=.false.
106        endif
107      ENDIF
108
109c
110c-----------------------------------------------------------------------
111c   detection des profils a modifier:
112c   ---------------------------------
113c   si le profil est a modifier
114c   (i.e. ph(niv_sup) < ph(niv_inf) )
115c   alors le tableau "vtest" est mis a .TRUE. ;
116c   sinon, il reste a sa valeur initiale (.FALSE.)
117c   cette operation est vectorisable
118c   On en profite pour copier la valeur initiale de "ph"
119c   dans le champ de travail "zh"
120
121
122      DO l=1,nlay
123         DO ig=1,ngrid
124            zh(ig,l)=ph(ig,l)+pdhfi(ig,l)*ptimestep
125            zu(ig,l)=pu(ig,l)+pdufi(ig,l)*ptimestep
126            zv(ig,l)=pv(ig,l)+pdvfi(ig,l)*ptimestep
127         ENDDO
128      ENDDO
129
130      if(tracer) then     
131        DO iq =1, nq
132         DO l=1,nlay
133           DO ig=1,ngrid
134              zq(ig,l,iq)=pq(ig,l,iq)+pdqfi(ig,l,iq)*ptimestep
135           ENDDO
136         ENDDO
137        ENDDO
138      end if
139
140
141      CALL scopy(ngrid*nlay,zh,1,zh2,1)
142      CALL scopy(ngrid*nlay,zu,1,zu2,1)
143      CALL scopy(ngrid*nlay,zv,1,zv2,1)
144      CALL scopy(ngrid*nlay*nq,zq,1,zq2,1)
145
146      DO ig=1,ngrid
147        vtest(ig)=.FALSE.
148      ENDDO
149c
150      if (ico2.ne.0) then
151c        Special case if one of the tracer is CO2 gas
152         DO l=1,nlay
153           DO ig=1,ngrid
154             zhc(ig,l) = zh2(ig,l)*(A*zq2(ig,l,ico2)+B)
155           ENDDO
156         ENDDO
157       else
158          CALL scopy(ngrid*nlay,zh2,1,zhc,1)
159       end if
160
161       
162
163      DO l=2,nlay
164        DO ig=1,ngrid
165          IF(zhc(ig,l).LT.zhc(ig,l-1)) vtest(ig)=.TRUE.
166        ENDDO
167      ENDDO
168c
169      jcnt=0
170      DO ig=1,ngrid
171         IF(vtest(ig)) THEN
172            jcnt=jcnt+1
173            jadrs(jcnt)=ig
174         ENDIF
175      ENDDO
176
177
178c-----------------------------------------------------------------------
179c  Ajustement des "jcnt" profils instables indices par "jadrs":
180c  ------------------------------------------------------------
181c
182      DO jj = 1, jcnt   ! loop on every convective grid point
183c
184          i = jadrs(jj)
185 
186c   Calcul des niveaux sigma sur cette colonne
187          DO l=1,nlay+1
188            sig(l)=pplev(i,l)/pplev(i,1)
189       
190          ENDDO
191         DO l=1,nlay
192            dsig(l)=sig(l)-sig(l+1)
193            sdsig(l)=ppopsk(i,l)*dsig(l)
194         ENDDO
195          l2 = 1
196c
197c      -- boucle de sondage vers le haut
198c
199cins$     Loop  vers le haut sur l2
200          DO
201c
202            l2 = l2 + 1
203            IF (l2 .GT. nlay) EXIT
204            IF (zhc(i, l2) .LT. zhc(i, l2-1)) THEN
205 
206c          -- l2 est le niveau le plus haut de la colonne instable
207 
208              l1 = l2 - 1
209              l  = l1
210              zsm = sdsig(l2)
211              zdsm = dsig(l2)
212              zhm = zh2(i, l2)
213              if(ico2.ne.0) zqco2m = zq2(i,l2,ico2)
214c
215c          -- boucle de sondage vers le bas
216c             Loop
217              DO
218c
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 
230c            -- doit on etendre la colonne vers le bas ?
231 
232                down = .FALSE.
233                IF (l1 .NE. 1) THEN    !--  and then
234                  IF (zhmc .LT. zhc(i, l1-1)) THEN
235                    down = .TRUE.
236                  END IF
237                END IF
238 
239                IF (down) THEN
240 
241                  l1 = l1 - 1
242                  l  = l1
243 
244                ELSE
245 
246c              -- peut on etendre la colonne vers le haut ?
247 
248                  IF (l2 .EQ. nlay) EXIT
249 
250                  IF (zhc(i, l2+1) .GE. zhmc) EXIT
251c
252                  l2 = l2 + 1
253                  l  = l2
254c
255                END IF
256c
257cins$         End Loop
258              ENDDO
259c
260c          -- nouveau profil : constant (valeur moyenne)
261c
262              zalpha=0.
263              zum=0.
264              zvm=0.
265              do iq=1,nq
266                zqm(iq) = 0.
267              end do
268              DO l = l1, l2
269                if(ico2.ne.0) then
270                  zalpha=zalpha+
271     &            ABS(zhc(i,l)/(A+B*zqco2m) -zhm)*dsig(l)
272                else
273                  zalpha=zalpha+ABS(zh2(i,l)-zhm)*dsig(l)
274                endif
275                zh2(i, l) = zhm
276                zum=zum+dsig(l)*zu(i,l)
277                zvm=zvm+dsig(l)*zv(i,l)
278                do iq=1,nq
279                   zqm(iq) = zqm(iq)+dsig(l)*zq(i,l,iq)
280                end do
281              ENDDO
282              zalpha=zalpha/(zhm*(sig(l1)-sig(l2+1)))
283              zum=zum/(sig(l1)-sig(l2+1))
284              zvm=zvm/(sig(l1)-sig(l2+1))
285              do iq=1,nq
286                 zqm(iq) = zqm(iq)/(sig(l1)-sig(l2+1))
287              end do
288
289              IF(zalpha.GT.1.) THEN
290                 zalpha=1.
291              ELSE
292c                IF(zalpha.LT.0.) STOP
293                 IF(zalpha.LT.1.e-4) zalpha=1.e-4
294              ENDIF
295
296              DO l=l1,l2
297                 zu2(i,l)=zu2(i,l)+zalpha*(zum-zu2(i,l))
298                 zv2(i,l)=zv2(i,l)+zalpha*(zvm-zv2(i,l))
299                 do iq=1,nq
300c                  zq2(i,l,iq)=zq2(i,l,iq)+zalpha*(zqm(iq)-zq2(i,l,iq))
301                   zq2(i,l,iq)=zqm(iq)
302                 end do
303              ENDDO
304c              diag_alpha(i)=zalpha  !temporaire
305              if (ico2.ne.0) then
306                DO l=l1, l2
307                  zhc(i,l) = zh2(i,l)*(A*zq2(i,l,ico2)+B)
308                ENDDO
309              end if
310
311 
312              l2 = l2 + 1
313c
314            END IF   ! fin traitement instabilité entre l1 et l2.
315c                      On repart pour test à partir du l2 au dessus...
316          ENDDO   ! End Loop sur l2 vers le haut
317c
318      ENDDO
319c
320      DO l=1,nlay
321        DO ig=1,ngrid
322          pdhadj(ig,l)=(zh2(ig,l)-zh(ig,l))/ptimestep
323          pduadj(ig,l)=(zu2(ig,l)-zu(ig,l))/ptimestep
324          pdvadj(ig,l)=(zv2(ig,l)-zv(ig,l))/ptimestep
325        ENDDO
326      ENDDO
327
328      if(tracer) then
329        do iq=1, nq
330          do  l=1,nlay
331            do ig=1, ngrid
332              pdqadj(ig,l,iq)=(zq2(ig,l,iq)-zq(ig,l,iq))/ptimestep
333            end do
334          end do
335        end do
336      end if
337
338c     outpu
339      if (ngrid.eq.1) then
340         ig=1
341         iq =1
342         write(*,*)'**** l, pq(ig,l,iq),zq(ig,l,iq),zq2(ig,l,iq)' 
343         do l=nlay,1,-1
344           write(*,*) l, pq(ig,l,iq),zq(ig,l,iq),zq2(ig,l,iq)
345         end do
346      end if
347
348
349      RETURN
350      END
Note: See TracBrowser for help on using the repository browser.