source: LMDZ4/trunk/libf/dyn3d/advtrac.F @ 524

Last change on this file since 524 was 524, checked in by lmdzadmin, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 12.2 KB
Line 
1!
2! $Header$
3!
4c
5c
6#ifdef INCA_CH4
7      SUBROUTINE advtrac(pbaru,pbarv ,
8     *                   p,  masse,q,iapptrac,teta,
9     *                  flxw,
10     *                  pk,
11     *                  mmt_adj,
12     *                  hadv_flg)
13#else
14      SUBROUTINE advtrac(pbaru,pbarv ,
15     *                   p,  masse,q,iapptrac,teta,
16     *                  pk)
17#endif
18
19c     Auteur :  F. Hourdin
20c
21c     Modif. P. Le Van     (20/12/97)
22c            F. Codron     (10/99)
23c            D. Le Croller (07/2001)
24c            M.A Filiberti (04/2002)
25c
26      IMPLICIT NONE
27c
28#include "dimensions.h"
29#include "paramet.h"
30#include "comconst.h"
31#include "comvert.h"
32#include "comdissip.h"
33#include "comgeom2.h"
34#include "logic.h"
35#include "temps.h"
36#include "control.h"
37#include "ener.h"
38#include "description.h"
39#include "advtrac.h"
40
41c-------------------------------------------------------------------
42c     Arguments
43c-------------------------------------------------------------------
44c     Ajout PPM
45c--------------------------------------------------------
46      REAL massebx(ip1jmp1,llm),masseby(ip1jm,llm)
47c--------------------------------------------------------
48      INTEGER iapptrac
49      REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm)
50      REAL q(ip1jmp1,llm,nqmx),masse(ip1jmp1,llm)
51      REAL p( ip1jmp1,llmp1 ),teta(ip1jmp1,llm)
52      REAL pk(ip1jmp1,llm)
53#ifdef INCA_CH4
54      INTEGER            :: hadv_flg(nq)
55      REAL               :: mmt_adj(ip1jmp1,llm)
56      REAL               :: flxw(ip1jmp1,llm)
57#endif
58
59c-------------------------------------------------------------
60c     Variables locales
61c-------------------------------------------------------------
62
63      REAL pbaruc(ip1jmp1,llm),pbarvc(ip1jm,llm)
64      REAL massem(ip1jmp1,llm),zdp(ip1jmp1)
65      REAL pbarug(ip1jmp1,llm),pbarvg(ip1jm,llm),wg(ip1jmp1,llm)
66      REAL (kind=kind(1.d0)) :: t_initial, t_final, tps_cpu
67      real cpuadv(nqmx)
68      common/cpuadv/cpuadv
69
70      INTEGER iadvtr
71      INTEGER ij,l,iq,iiq
72      REAL zdpmin, zdpmax
73      EXTERNAL  minmax
74      SAVE iadvtr, massem, pbaruc, pbarvc
75      DATA iadvtr/0/
76c----------------------------------------------------------
77c     Rajouts pour PPM
78c----------------------------------------------------------
79      INTEGER indice,n
80      REAL dtbon ! Pas de temps adaptatif pour que CFL<1
81      REAL CFLmaxz,aaa,bbb ! CFL maximum
82      REAL psppm(iim,jjp1) ! pression  au sol
83      REAL unatppm(iim,jjp1,llm),vnatppm(iim,jjp1,llm)
84      REAL qppm(iim*jjp1,llm,nqmx)
85      REAL fluxwppm(iim,jjp1,llm)
86      REAL apppm(llmp1), bpppm(llmp1)
87      LOGICAL dum,fill
88      DATA fill/.true./
89      DATA dum/.true./
90
91
92      IF(iadvtr.EQ.0) THEN
93         CALL initial0(ijp1llm,pbaruc)
94         CALL initial0(ijmllm,pbarvc)
95      ENDIF
96
97c   accumulation des flux de masse horizontaux
98      DO l=1,llm
99         DO ij = 1,ip1jmp1
100            pbaruc(ij,l) = pbaruc(ij,l) + pbaru(ij,l)
101         ENDDO
102         DO ij = 1,ip1jm
103            pbarvc(ij,l) = pbarvc(ij,l) + pbarv(ij,l)
104         ENDDO
105      ENDDO
106
107c   selection de la masse instantannee des mailles avant le transport.
108      IF(iadvtr.EQ.0) THEN
109
110         CALL SCOPY(ip1jmp1*llm,masse,1,massem,1)
111ccc         CALL filtreg ( massem ,jjp1, llm,-2, 2, .TRUE., 1 )
112c
113      ENDIF
114
115      iadvtr   = iadvtr+1
116      iapptrac = iadvtr
117
118
119c   Test pour savoir si on advecte a ce pas de temps
120      IF ( iadvtr.EQ.iapp_tracvl ) THEN
121
122cc   ..  Modif P.Le Van  ( 20/12/97 )  ....
123cc
124
125c   traitement des flux de masse avant advection.
126c     1. calcul de w
127c     2. groupement des mailles pres du pole.
128
129        CALL groupe( massem, pbaruc,pbarvc, pbarug,pbarvg,wg )
130
131#ifdef INCA_CH4
132      ! ... Flux de masse diaganostiques traceurs
133      flxw = wg / FLOAT(iapp_tracvl)
134#endif
135
136c  test sur l'eventuelle creation de valeurs negatives de la masse
137         DO l=1,llm-1
138            DO ij = iip2+1,ip1jm
139              zdp(ij) =    pbarug(ij-1,l)   - pbarug(ij,l)
140     s                  - pbarvg(ij-iip1,l) + pbarvg(ij,l)
141     s                  +       wg(ij,l+1)  - wg(ij,l)
142            ENDDO
143            CALL SCOPY( jjm -1 ,zdp(iip1+iip1),iip1,zdp(iip2),iip1 )
144            DO ij = iip2,ip1jm
145               zdp(ij)= zdp(ij)*dtvr/ massem(ij,l)
146            ENDDO
147
148
149            CALL minmax ( ip1jm-iip1, zdp(iip2), zdpmin,zdpmax )
150
151            IF(MAX(ABS(zdpmin),ABS(zdpmax)).GT.0.5) THEN
152            PRINT*,'WARNING DP/P l=',l,'  MIN:',zdpmin,
153     s        '   MAX:', zdpmax
154            ENDIF
155
156         ENDDO
157
158c-------------------------------------------------------------------
159c   Advection proprement dite (Modification Le Croller (07/2001)
160c-------------------------------------------------------------------
161
162c----------------------------------------------------
163c        Calcul des moyennes basées sur la masse
164c----------------------------------------------------
165          call massbar(massem,massebx,masseby)         
166
167c-----------------------------------------------------------
168c     Appel des sous programmes d'advection
169c-----------------------------------------------------------
170      do iq=1,nqmx
171c        call clock(t_initial)
172        if(iadv(iq) == 0) cycle
173c   ----------------------------------------------------------------
174c   Schema de Van Leer I MUSCL
175c   ----------------------------------------------------------------
176        if(iadv(iq).eq.10) THEN
177            call vlsplt(q(1,1,iq),2.,massem,wg,pbarug,pbarvg,dtvr)
178
179
180c   ----------------------------------------------------------------
181c   Schema "pseudo amont" + test sur humidite specifique
182C    pour la vapeur d'eau. F. Codron
183c   ----------------------------------------------------------------
184        else if(iadv(iq).eq.14) then
185c
186           CALL vlspltqs( q(1,1,1), 2., massem, wg ,
187     *                 pbarug,pbarvg,dtvr,p,pk,teta )
188c   ----------------------------------------------------------------
189c   Schema de Frederic Hourdin
190c   ----------------------------------------------------------------
191        else if(iadv(iq).eq.12) then
192c            Pas de temps adaptatif
193           call adaptdt(iadv(iq),dtbon,n,pbarug,massem)
194           if (n.GT.1) then
195           write(*,*) 'WARNING horizontal dt=',dtbon,'dtvr=',
196     s             dtvr,'n=',n
197           endif
198           do indice=1,n
199            call advn(q(1,1,iq),massem,wg,pbarug,pbarvg,dtbon,1)
200           end do
201        else if(iadv(iq).eq.13) then
202c            Pas de temps adaptatif
203           call adaptdt(iadv(iq),dtbon,n,pbarug,massem)
204           if (n.GT.1) then
205           write(*,*) 'WARNING horizontal dt=',dtbon,'dtvr=',
206     s             dtvr,'n=',n
207           endif
208          do indice=1,n
209            call advn(q(1,1,iq),massem,wg,pbarug,pbarvg,dtbon,2)
210          end do
211c   ----------------------------------------------------------------
212c   Schema de pente SLOPES
213c   ----------------------------------------------------------------
214        else if (iadv(iq).eq.20) then
215            call pentes_ini (q(1,1,iq),wg,massem,pbarug,pbarvg,0)
216#ifdef INCA_CH4
217       do iiq = iq+1, iq+3
218         q(:,:,iiq)=q(:,:,iiq)*mmt_adj(:,:,1)
219       enddo
220#endif
221
222c   ----------------------------------------------------------------
223c   Schema de Prather
224c   ----------------------------------------------------------------
225        else if (iadv(iq).eq.30) then
226c            Pas de temps adaptatif
227           call adaptdt(iadv(iq),dtbon,n,pbarug,massem)
228           if (n.GT.1) then
229           write(*,*) 'WARNING horizontal dt=',dtbon,'dtvr=',
230     s             dtvr,'n=',n
231           endif
232           call  prather(q(1,1,iq),wg,massem,pbarug,pbarvg,
233     s                     n,dtbon)
234#ifdef INCA_CH4
235       do iiq = iq+1, iq+9
236         q(:,:,iiq)=q(:,:,iiq)*mmt_adj(:,:,1)
237       enddo
238#endif
239c   ----------------------------------------------------------------
240c   Schemas PPM Lin et Rood
241c   ----------------------------------------------------------------
242         else if (iadv(iq).eq.11.OR.(iadv(iq).GE.16.AND.
243     s                     iadv(iq).LE.18)) then
244
245c        Test sur le flux horizontal
246c        Pas de temps adaptatif
247         call adaptdt(iadv(iq),dtbon,n,pbarug,massem)
248         if (n.GT.1) then
249         write(*,*) 'WARNING horizontal dt=',dtbon,'dtvr=',
250     s             dtvr,'n=',n
251         endif
252c        Test sur le flux vertical
253         CFLmaxz=0.
254         do l=2,llm
255           do ij=iip2,ip1jm
256            aaa=wg(ij,l)*dtvr/massem(ij,l)
257            CFLmaxz=max(CFLmaxz,aaa)
258            bbb=-wg(ij,l)*dtvr/massem(ij,l-1)
259            CFLmaxz=max(CFLmaxz,bbb)
260           enddo
261         enddo
262         if (CFLmaxz.GE.1) then
263            write(*,*) 'WARNING vertical','CFLmaxz=', CFLmaxz
264         endif
265
266c-----------------------------------------------------------
267c        Ss-prg interface LMDZ.4->PPM3d
268c-----------------------------------------------------------
269
270          call interpre(q(1,1,iq),qppm(1,1,iq),wg,fluxwppm,massem,
271     s                 apppm,bpppm,massebx,masseby,pbarug,pbarvg,
272     s                 unatppm,vnatppm,psppm)
273
274          do indice=1,n
275c---------------------------------------------------------------------
276c                         VL (version PPM) horiz. et PPM vert.
277c---------------------------------------------------------------------
278                if (iadv(iq).eq.11) then
279c                  Ss-prg PPM3d de Lin
280                  call ppm3d(1,qppm(1,1,iq),
281     s                       psppm,psppm,
282     s                       unatppm,vnatppm,fluxwppm,dtbon,2,2,2,1,
283     s                       iim,jjp1,2,llm,apppm,bpppm,0.01,6400000,
284     s                       fill,dum,220.)
285
286c----------------------------------------------------------------------
287c                           Monotonic PPM
288c----------------------------------------------------------------------
289               else if (iadv(iq).eq.16) then
290c                  Ss-prg PPM3d de Lin
291                  call ppm3d(1,qppm(1,1,iq),
292     s                       psppm,psppm,
293     s                       unatppm,vnatppm,fluxwppm,dtbon,3,3,3,1,
294     s                       iim,jjp1,2,llm,apppm,bpppm,0.01,6400000,
295     s                       fill,dum,220.)
296c---------------------------------------------------------------------
297
298c---------------------------------------------------------------------
299c                           Semi Monotonic PPM
300c---------------------------------------------------------------------
301               else if (iadv(iq).eq.17) then
302c                  Ss-prg PPM3d de Lin
303                  call ppm3d(1,qppm(1,1,iq),
304     s                       psppm,psppm,
305     s                       unatppm,vnatppm,fluxwppm,dtbon,4,4,4,1,
306     s                       iim,jjp1,2,llm,apppm,bpppm,0.01,6400000,
307     s                       fill,dum,220.)
308c---------------------------------------------------------------------
309
310c---------------------------------------------------------------------
311c                         Positive Definite PPM
312c---------------------------------------------------------------------
313                else if (iadv(iq).eq.18) then
314c                  Ss-prg PPM3d de Lin
315                  call ppm3d(1,qppm(1,1,iq),
316     s                       psppm,psppm,
317     s                       unatppm,vnatppm,fluxwppm,dtbon,5,5,5,1,
318     s                       iim,jjp1,2,llm,apppm,bpppm,0.01,6400000,
319     s                       fill,dum,220.)
320c---------------------------------------------------------------------
321                endif
322            enddo
323c-----------------------------------------------------------------
324c               Ss-prg interface PPM3d-LMDZ.4
325c-----------------------------------------------------------------
326                  call interpost(q(1,1,iq),qppm(1,1,iq))
327            endif
328c----------------------------------------------------------------------
329
330c-----------------------------------------------------------------
331c On impose une seule valeur du traceur au pôle Sud j=jjm+1=jjp1
332c et Nord j=1
333c-----------------------------------------------------------------
334
335c                  call traceurpole(q(1,1,iq),massem)
336
337c calcul du temps cpu pour un schema donne
338
339c                  call clock(t_final)
340                  tps_cpu=t_final-t_initial
341                  cpuadv(iq)=cpuadv(iq)+tps_cpu
342
343       end DO
344
345
346c------------------------------------------------------------------
347c   on reinitialise a zero les flux de masse cumules
348c---------------------------------------------------
349          iadvtr=0
350
351       ENDIF ! if iadvtr.EQ.iapp_tracvl
352
353       RETURN
354       END
355
Note: See TracBrowser for help on using the repository browser.