source: LMDZ4/trunk/libf/dyn3d/leapfrog.F @ 559

Last change on this file since 559 was 559, checked in by lmdzadmin, 21 years ago

Initialisations diverses YM
LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 19.1 KB
Line 
1!
2! $Header$
3!
4c
5c
6      SUBROUTINE leapfrog(ucov,vcov,teta,ps,masse,phis,nq,q,clesphy0,
7     &                    time_0)
8
9#ifdef INCA
10      USE transport_controls, ONLY : hadv_flg, mmt_adj
11#endif
12
13      IMPLICIT NONE
14
15c      ......   Version  du 10/01/98    ..........
16
17c             avec  coordonnees  verticales hybrides
18c   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
19
20c=======================================================================
21c
22c   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
23c   -------
24c
25c   Objet:
26c   ------
27c
28c   GCM LMD nouvelle grille
29c
30c=======================================================================
31c
32c  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
33c      et possibilite d'appeler une fonction f(y)  a derivee tangente
34c      hyperbolique a la  place de la fonction a derivee sinusoidale.
35
36c  ... Possibilite de choisir le shema pour l'advection de
37c        q  , en modifiant iadv dans traceur.def  (10/02) .
38c
39c      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
40c      Pour Van-Leer iadv=10
41c
42c-----------------------------------------------------------------------
43c   Declarations:
44c   -------------
45
46#include "dimensions.h"
47#include "paramet.h"
48#include "comconst.h"
49#include "comdissnew.h"
50#include "comvert.h"
51#include "comgeom.h"
52#include "logic.h"
53#include "temps.h"
54#include "control.h"
55#include "ener.h"
56#include "description.h"
57#include "serre.h"
58#include "com_io_dyn.h"
59#include "iniprint.h"
60
61c#include "tracstoke.h"
62
63#include "academic.h"
64
65      integer nq
66
67      INTEGER         longcles
68      PARAMETER     ( longcles = 20 )
69      REAL  clesphy0( longcles )
70
71      real zqmin,zqmax
72      INTEGER nbetatmoy, nbetatdem,nbetat
73
74c   variables dynamiques
75      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
76      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
77      REAL q(ip1jmp1,llm,nqmx)               ! champs advectes
78      REAL ps(ip1jmp1)                       ! pression  au sol
79      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
80      REAL pks(ip1jmp1)                      ! exner au  sol
81      REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
82      REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
83      REAL masse(ip1jmp1,llm)                ! masse d'air
84      REAL phis(ip1jmp1)                     ! geopotentiel au sol
85      REAL phi(ip1jmp1,llm)                  ! geopotentiel
86      REAL w(ip1jmp1,llm)                    ! vitesse verticale
87
88c variables dynamiques intermediaire pour le transport
89      REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm) !flux de masse
90
91c   variables dynamiques au pas -1
92      REAL vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm)
93      REAL tetam1(ip1jmp1,llm),psm1(ip1jmp1)
94      REAL massem1(ip1jmp1,llm)
95
96c   tendances dynamiques
97      REAL dv(ip1jm,llm),du(ip1jmp1,llm)
98      REAL dteta(ip1jmp1,llm),dq(ip1jmp1,llm,nqmx),dp(ip1jmp1)
99
100c   tendances de la dissipation
101      REAL dvdis(ip1jm,llm),dudis(ip1jmp1,llm)
102      REAL dtetadis(ip1jmp1,llm)
103
104c   tendances physiques
105      REAL dvfi(ip1jm,llm),dufi(ip1jmp1,llm)
106      REAL dtetafi(ip1jmp1,llm),dqfi(ip1jmp1,llm,nqmx),dpfi(ip1jmp1)
107
108c   variables pour le fichier histoire
109      REAL dtav      ! intervalle de temps elementaire
110
111      REAL tppn(iim),tpps(iim),tpn,tps
112c
113      INTEGER itau,itaufinp1,iav
114      INTEGER*4  iday ! jour julien
115      REAL       time ! Heure de la journee en fraction d'1 jour
116
117      REAL  SSUM
118      REAL time_0 , finvmaold(ip1jmp1,llm)
119
120      LOGICAL lafin
121      INTEGER ij,iq,l
122      INTEGER ik
123
124      real time_step, t_wrt, t_ops
125
126      REAL rdayvrai,rdaym_ini
127      LOGICAL first,callinigrads
128
129      data callinigrads/.true./
130      character*10 string10
131
132      REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm)
133#ifdef INCA_CH4
134      REAL :: flxw(ip1jmp1,llm)
135#endif
136
137c+jld variables test conservation energie
138      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
139C     Tendance de la temp. potentiel d (theta)/ d t due a la
140C     tansformation d'energie cinetique en energie thermique
141C     cree par la dissipation
142      REAL dtetaecdt(ip1jmp1,llm)
143      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
144      REAL vnat(ip1jm,llm),unat(ip1jmp1,llm)
145      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
146      CHARACTER*15 ztit
147      INTEGER   ip_ebil_dyn  ! PRINT level for energy conserv. diag.
148      SAVE      ip_ebil_dyn
149      DATA      ip_ebil_dyn/0/
150c-jld
151
152      character*80 dynhist_file, dynhistave_file
153      character*20 modname
154      character*80 abort_message
155
156C Calendrier
157      LOGICAL true_calendar
158      PARAMETER (true_calendar = .false.)
159
160      logical dissip_conservative
161      save dissip_conservative
162      data dissip_conservative/.true./
163
164      LOGICAL prem
165      save prem
166      DATA prem/.true./
167      INTEGER testita
168      PARAMETER (testita = 9)
169
170      itaufin   = nday*day_step
171      itaufinp1 = itaufin +1
172
173
174      itau = 0
175      iday = day_ini+itau/day_step
176      time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
177         IF(time.GT.1.) THEN
178          time = time-1.
179          iday = iday+1
180         ENDIF
181
182
183c-----------------------------------------------------------------------
184c   On initialise la pression et la fonction d'Exner :
185c   --------------------------------------------------
186
187      dq=0.
188      CALL pression ( ip1jmp1, ap, bp, ps, p       )
189      CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
190
191c-----------------------------------------------------------------------
192c   Debut de l'integration temporelle:
193c   ----------------------------------
194
195   1  CONTINUE
196
197
198#ifdef CPP_IOIPSL
199      if (ok_guide.and.(itaufin-itau-1)*dtvr.gt.21600) then
200        call guide(itau,ucov,vcov,teta,q,masse,ps)
201      else
202        IF(prt_level>9)WRITE(*,*)'attention on ne guide pas les ',
203     .    '6 dernieres heures'
204      endif
205#endif
206c
207c     IF( MOD( itau, 10* day_step ).EQ.0 )  THEN
208c       CALL  test_period ( ucov,vcov,teta,q,p,phis )
209c       PRINT *,' ----   Test_period apres continue   OK ! -----', itau
210c     ENDIF
211c
212      CALL SCOPY( ijmllm ,vcov , 1, vcovm1 , 1 )
213      CALL SCOPY( ijp1llm,ucov , 1, ucovm1 , 1 )
214      CALL SCOPY( ijp1llm,teta , 1, tetam1 , 1 )
215      CALL SCOPY( ijp1llm,masse, 1, massem1, 1 )
216      CALL SCOPY( ip1jmp1, ps  , 1,   psm1 , 1 )
217
218      forward = .TRUE.
219      leapf   = .FALSE.
220      dt      =  dtvr
221
222c   ...    P.Le Van .26/04/94  ....
223
224      CALL SCOPY   ( ijp1llm,   masse, 1, finvmaold,     1 )
225      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
226
227      call minmax(ijp1llm,q(:,:,3),zqmin,zqmax)
228
229   2  CONTINUE
230
231c-----------------------------------------------------------------------
232
233c   date:
234c   -----
235
236
237c   gestion des appels de la physique et des dissipations:
238c   ------------------------------------------------------
239c
240c   ...    P.Le Van  ( 6/02/95 )  ....
241
242      apphys = .FALSE.
243      statcl = .FALSE.
244      conser = .FALSE.
245      apdiss = .FALSE.
246
247      IF( purmats ) THEN
248         IF( MOD(itau,iconser) .EQ.0.AND.  forward    ) conser = .TRUE.
249         IF( MOD(itau,idissip ).EQ.0.AND..NOT.forward ) apdiss = .TRUE.
250         IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward
251     s          .and. iflag_phys.NE.0                 ) apphys = .TRUE.
252      ELSE
253         IF( MOD(itau   ,iconser) .EQ. 0              ) conser = .TRUE.
254         IF( MOD(itau+1,idissip)  .EQ. 0              ) apdiss = .TRUE.
255         IF( MOD(itau+1,iphysiq).EQ.0.AND.iflag_phys.NE.0) apphys=.TRUE.
256      END IF
257
258c-----------------------------------------------------------------------
259c   calcul des tendances dynamiques:
260c   --------------------------------
261
262      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
263
264      CALL caldyn
265     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
266     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time+iday-day_ini )
267
268c-----------------------------------------------------------------------
269c   calcul des tendances advection des traceurs (dont l'humidite)
270c   -------------------------------------------------------------
271
272      IF( forward. OR . leapf )  THEN
273
274c
275#ifdef INCA_CH4
276             CALL caladvtrac(q,pbaru,pbarv,
277     *                      p, masse, dq,  teta,
278     .             flxw,
279     .             pk,
280     .             mmt_adj,
281     .             hadv_flg)
282#else
283             CALL caladvtrac(q,pbaru,pbarv,
284     *                      p, masse, dq,  teta,
285     .             pk)
286#endif
287
288         IF (offline) THEN
289Cmaf stokage du flux de masse pour traceurs OFF-LINE
290
291#ifdef CPP_IOIPSL
292           CALL fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
293     .   dtvr, itau)
294#endif
295
296
297         ENDIF
298c
299      ENDIF
300
301
302c-----------------------------------------------------------------------
303c   integrations dynamique et traceurs:
304c   ----------------------------------
305
306
307       CALL integrd ( 2,vcovm1,ucovm1,tetam1,psm1,massem1 ,
308     $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,
309     $              finvmaold                                    )
310
311
312c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
313c
314c-----------------------------------------------------------------------
315c   calcul des tendances physiques:
316c   -------------------------------
317c    ########   P.Le Van ( Modif le  6/02/95 )   ###########
318c
319       IF( purmats )  THEN
320          IF( itau.EQ.itaufin.AND..NOT.forward ) lafin = .TRUE.
321       ELSE
322          IF( itau+1. EQ. itaufin )              lafin = .TRUE.
323       ENDIF
324c
325c
326       IF( apphys )  THEN
327c
328c     .......   Ajout   P.Le Van ( 17/04/96 )   ...........
329c
330
331         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
332         CALL exner_hyb(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
333
334           rdaym_ini  = itau * dtvr / daysec
335           rdayvrai   = rdaym_ini  + day_ini
336
337
338c rajout debug
339c       lafin = .true.
340
341
342c   Inbterface avec les routines de phylmd (phymars ... )
343c   -----------------------------------------------------
344
345#ifdef CPP_PHYS
346c+jld
347
348c  Diagnostique de conservation de l'énergie : initialisation
349      IF (ip_ebil_dyn.ge.1 ) THEN
350          ztit='bil dyn'
351          CALL diagedyn(ztit,2,1,1,dtphys
352     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2))
353      ENDIF
354c-jld
355
356        CALL calfis( nq, lafin ,rdayvrai,time  ,
357     $               ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
358     $               du,dv,dteta,dq,w,
359#ifdef INCA_CH4
360     $               flxw,
361#endif
362     $               clesphy0, dufi,dvfi,dtetafi,dqfi,dpfi  )
363
364c      ajout des tendances physiques:
365c      ------------------------------
366          CALL addfi( nqmx, dtphys, leapf, forward   ,
367     $                  ucov, vcov, teta , q   ,ps ,
368     $                 dufi, dvfi, dtetafi , dqfi ,dpfi  )
369c
370c  Diagnostique de conservation de l'énergie : difference
371      IF (ip_ebil_dyn.ge.1 ) THEN
372          ztit='bil phys'
373          CALL diagedyn(ztit,2,1,1,dtphys
374     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2))
375      ENDIF
376#else
377
378c   Calcul academique de la physique = Rappel Newtonien + fritcion
379c   --------------------------------------------------------------
380       teta(:,:)=teta(:,:)
381     s  -iphysiq*dtvr*(teta(:,:)-tetarappel(:,:))/taurappel
382       call friction(ucov,vcov,iphysiq*dtvr)
383
384#endif
385
386c-jld
387       ENDIF
388
389        CALL pression ( ip1jmp1, ap, bp, ps, p                  )
390        CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
391
392
393c-----------------------------------------------------------------------
394c   dissipation horizontale et verticale  des petites echelles:
395c   ----------------------------------------------------------
396
397      IF(apdiss) THEN
398
399
400c   calcul de l'energie cinetique avant dissipation
401        call covcont(llm,ucov,vcov,ucont,vcont)
402        call enercin(vcov,ucov,vcont,ucont,ecin0)
403
404c   dissipation
405        CALL dissip(vcov,ucov,teta,p,dvdis,dudis,dtetadis)
406        ucov=ucov+dudis
407        vcov=vcov+dvdis
408c       teta=teta+dtetadis
409
410
411c------------------------------------------------------------------------
412        if (dissip_conservative) then
413C       On rajoute la tendance due a la transform. Ec -> E therm. cree
414C       lors de la dissipation
415            call covcont(llm,ucov,vcov,ucont,vcont)
416            call enercin(vcov,ucov,vcont,ucont,ecin)
417            dtetaecdt= (ecin0-ecin)/ pk
418c           teta=teta+dtetaecdt
419            dtetadis=dtetadis+dtetaecdt
420        endif
421        teta=teta+dtetadis
422c------------------------------------------------------------------------
423
424
425c    .......        P. Le Van (  ajout  le 17/04/96  )   ...........
426c   ...      Calcul de la valeur moyenne, unique de h aux poles  .....
427c
428
429        DO l  =  1, llm
430          DO ij =  1,iim
431           tppn(ij)  = aire(  ij    ) * teta(  ij    ,l)
432           tpps(ij)  = aire(ij+ip1jm) * teta(ij+ip1jm,l)
433          ENDDO
434           tpn  = SSUM(iim,tppn,1)/apoln
435           tps  = SSUM(iim,tpps,1)/apols
436
437          DO ij = 1, iip1
438           teta(  ij    ,l) = tpn
439           teta(ij+ip1jm,l) = tps
440          ENDDO
441        ENDDO
442
443        DO ij =  1,iim
444          tppn(ij)  = aire(  ij    ) * ps (  ij    )
445          tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
446        ENDDO
447          tpn  = SSUM(iim,tppn,1)/apoln
448          tps  = SSUM(iim,tpps,1)/apols
449
450        DO ij = 1, iip1
451          ps(  ij    ) = tpn
452          ps(ij+ip1jm) = tps
453        ENDDO
454
455
456      END IF
457
458c ajout debug
459c              IF( lafin ) then 
460c                abort_message = 'Simulation finished'
461c                call abort_gcm(modname,abort_message,0)
462c              ENDIF
463       
464c   ********************************************************************
465c   ********************************************************************
466c   .... fin de l'integration dynamique  et physique pour le pas itau ..
467c   ********************************************************************
468c   ********************************************************************
469
470c   preparation du pas d'integration suivant  ......
471
472      IF ( .NOT.purmats ) THEN
473c       ........................................................
474c       ..............  schema matsuno + leapfrog  ..............
475c       ........................................................
476
477            IF(forward. OR. leapf) THEN
478              itau= itau + 1
479              iday= day_ini+itau/day_step
480              time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
481                IF(time.GT.1.) THEN
482                  time = time-1.
483                  iday = iday+1
484                ENDIF
485            ENDIF
486
487
488            IF( itau. EQ. itaufinp1 ) then 
489c$$$       write(79,*) 'ucov',ucov
490c$$$       write(80,*) 'vcov',vcov
491c$$$       write(81,*) 'teta',teta
492c$$$       write(82,*) 'ps',ps
493c$$$       write(83,*) 'q',q
494c$$$       WRITE(85,*) 'q1 = ',q(:,:,1)
495c$$$       WRITE(86,*) 'q3 = ',q(:,:,3)
496
497              abort_message = 'Simulation finished'
498
499              call abort_gcm(modname,abort_message,0)
500            ENDIF
501c-----------------------------------------------------------------------
502c   ecriture du fichier histoire moyenne:
503c   -------------------------------------
504
505            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
506               IF(itau.EQ.itaufin) THEN
507                  iav=1
508               ELSE
509                  iav=0
510               ENDIF
511#ifdef CPP_IOIPSL
512              CALL writedynav(histaveid, nqmx, itau,vcov ,
513     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
514               call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
515     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
516#endif
517
518            ENDIF
519
520c-----------------------------------------------------------------------
521c   ecriture de la bande histoire:
522c   ------------------------------
523
524            IF( MOD(itau,iecri         ).EQ.0) THEN
525c           IF( MOD(itau,iecri*day_step).EQ.0) THEN
526
527               nbetat = nbetatdem
528       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi        )
529        unat=0.
530        do l=1,llm
531           unat(iip2:ip1jm,l)=ucov(iip2:ip1jm,l)/cu(iip2:ip1jm)
532           vnat(:,l)=vcov(:,l)/cv(:)
533        enddo
534#ifdef CPP_IOIPSL
535c        CALL writehist(histid,histvid, nqmx,itau,vcov,
536c     s                       ucov,teta,phi,q,masse,ps,phis)
537#else
538#include "write_grads_dyn.h"
539#endif
540
541
542            ENDIF
543
544            IF(itau.EQ.itaufin) THEN
545
546
547#ifdef CPP_IOIPSL
548       CALL dynredem1("restart.nc",0.0,
549     ,                     vcov,ucov,teta,q,nqmx,masse,ps)
550#endif
551
552              CLOSE(99)
553            ENDIF
554
555c-----------------------------------------------------------------------
556c   gestion de l'integration temporelle:
557c   ------------------------------------
558
559            IF( MOD(itau,iperiod).EQ.0 )    THEN
560                    GO TO 1
561            ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
562
563                   IF( forward )  THEN
564c      fin du pas forward et debut du pas backward
565
566                      forward = .FALSE.
567                        leapf = .FALSE.
568                           GO TO 2
569
570                   ELSE
571c      fin du pas backward et debut du premier pas leapfrog
572
573                        leapf =  .TRUE.
574                        dt  =  2.*dtvr
575                        GO TO 2
576                   END IF
577            ELSE
578
579c      ......   pas leapfrog  .....
580
581                 leapf = .TRUE.
582                 dt  = 2.*dtvr
583                 GO TO 2
584            END IF
585
586      ELSE
587
588c       ........................................................
589c       ..............       schema  matsuno        ...............
590c       ........................................................
591            IF( forward )  THEN
592
593             itau =  itau + 1
594             iday = day_ini+itau/day_step
595             time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
596
597                  IF(time.GT.1.) THEN
598                   time = time-1.
599                   iday = iday+1
600                  ENDIF
601
602               forward =  .FALSE.
603               IF( itau. EQ. itaufinp1 ) then 
604                 abort_message = 'Simulation finished'
605                 call abort_gcm(modname,abort_message,0)
606               ENDIF
607               GO TO 2
608
609            ELSE
610
611            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
612               IF(itau.EQ.itaufin) THEN
613                  iav=1
614               ELSE
615                  iav=0
616               ENDIF
617#ifdef CPP_IOIPSL
618              CALL writedynav(histaveid, nqmx, itau,vcov ,
619     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
620               call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
621     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
622#endif
623
624            ENDIF
625
626               IF(MOD(itau,iecri         ).EQ.0) THEN
627c              IF(MOD(itau,iecri*day_step).EQ.0) THEN
628                  nbetat = nbetatdem
629       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi       )
630        unat=0.
631        do l=1,llm
632           unat(iip2:ip1jm,l)=ucov(iip2:ip1jm,l)/cu(iip2:ip1jm)
633           vnat(:,l)=vcov(:,l)/cv(:)
634        enddo
635#ifdef CPP_IOIPSL
636c       CALL writehist( histid, histvid, nqmx, itau,vcov ,
637c    ,                           ucov,teta,phi,q,masse,ps,phis)
638#else
639#include "write_grads_dyn.h"
640#endif
641
642
643               ENDIF
644
645#ifdef CPP_IOIPSL
646                 IF(itau.EQ.itaufin)
647     . CALL dynredem1("restart.nc",0.0,
648     .                     vcov,ucov,teta,q,nqmx,masse,ps)
649#endif
650
651                 forward = .TRUE.
652                 GO TO  1
653
654            ENDIF
655
656      END IF
657
658      STOP
659      END
Note: See TracBrowser for help on using the repository browser.