source: trunk/LMDZ.MARS/libf/dyn3d/gcm.F @ 937

Last change on this file since 937 was 828, checked in by tnavarro, 12 years ago

new option in run.def: ndynstep to run a number of dynamical time step. More efficient thannday for fractions of days

File size: 18.9 KB
Line 
1      PROGRAM gcm
2
3      IMPLICIT NONE
4
5c      ......   Version  du 10/01/98    ..........
6
7c             avec  coordonnees  verticales hybrides
8c   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
9
10c=======================================================================
11c
12c   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
13c   -------
14c
15c   Objet:
16c   ------
17c
18c   GCM LMD nouvelle grille
19c
20c=======================================================================
21c
22c  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
23c      et possibilite d'appeler une fonction f(y)  a derivee tangente
24c      hyperbolique a la  place de la fonction a derivee sinusoidale.
25
26c  ... Possibilite de choisir le shema de Van-leer pour l'advection de
27c        q  , en faisant iadv = 3  dans   traceur  (29/04/97) .
28c
29c      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
30c
31c-----------------------------------------------------------------------
32c   Declarations:
33c   -------------
34
35#include "dimensions.h"
36#include "paramet.h"
37#include "comconst.h"
38#include "comdissnew.h"
39#include "comvert.h"
40#include "comgeom.h"
41#include "logic.h"
42#include "temps.h"
43#include "control.h"
44#include "ener.h"
45#include "netcdf.inc"
46#include "description.h"
47#include "serre.h"
48#include "tracstoke.h"
49#include "sponge.h"
50#include"advtrac.h"
51
52      INTEGER*4  iday ! jour julien
53      REAL       time ! Heure de la journee en fraction d''1 jour
54      REAL zdtvr
55
56c   variables dynamiques
57      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
58      real, dimension(ip1jmp1,llm) :: teta   ! temperature potentielle
59      REAL q(ip1jmp1,llm,nqmx)               ! champs advectes
60      REAL ps(ip1jmp1)                       ! pression  au sol
61      REAL pext(ip1jmp1)                     ! pression  extensive
62      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
63      REAL pks(ip1jmp1)                      ! exner au  sol
64      REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
65      REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
66      REAL masse(ip1jmp1,llm)                ! masse d''air
67      REAL phis(ip1jmp1)                     ! geopotentiel au sol
68      REAL phi(ip1jmp1,llm)                  ! geopotentiel
69      REAL w(ip1jmp1,llm)                    ! vitesse verticale
70
71c variables dynamiques intermediaire pour le transport
72      REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm) !flux de masse
73
74c   variables dynamiques au pas -1
75      REAL vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm)
76
77      REAL tetam1(ip1jmp1,llm),psm1(ip1jmp1)
78      REAL massem1(ip1jmp1,llm)
79
80c   tendances dynamiques
81      REAL dv(ip1jm,llm),du(ip1jmp1,llm)
82      REAL dteta(ip1jmp1,llm),dq(ip1jmp1,llm,nqmx),dp(ip1jmp1)
83
84c   tendances de la dissipation
85      REAL dvdis(ip1jm,llm),dudis(ip1jmp1,llm)
86      REAL dhdis(ip1jmp1,llm)
87
88c   tendances physiques
89      REAL dvfi(ip1jm,llm),dufi(ip1jmp1,llm)
90      REAL dhfi(ip1jmp1,llm),dqfi(ip1jmp1,llm,nqmx),dpfi(ip1jmp1)
91
92c   variables pour le fichier histoire
93      REAL dtav      ! intervalle de temps elementaire
94
95      REAL tppn(iim),tpps(iim),tpn,tps
96c
97!      INTEGER iadv(nqmx) ! indice schema de transport pour le traceur iq
98
99      INTEGER itau,itaufinp1,iav
100
101
102      EXTERNAL caldyn, traceur
103      EXTERNAL dissip,geopot,iniconst,inifilr
104      EXTERNAL integrd,SCOPY
105      EXTERNAL inigeom
106      EXTERNAL exner_hyb,addit
107      EXTERNAL defrun_new, test_period
108      REAL  SSUM
109      REAL time_0 , finvmaold(ip1jmp1,llm)
110
111      LOGICAL lafin
112      INTEGER ij,iq,l,ierr,numvanle,iapp_tracvl
113
114      REAL rdayvrai,rdaym_ini,rday_ecri
115!      LOGICAL first
116      REAL beta(ip1jmp1,llm)
117
118      LOGICAL offline  ! Controle du stockage ds "fluxmass"
119      PARAMETER (offline=.false.)
120
121      character*20 modname
122      character*80 abort_message
123
124      LOGICAL tracer
125          data tracer/.true./
126      INTEGER nq
127
128C Calendrier
129      LOGICAL true_calendar
130      PARAMETER (true_calendar = .false.)
131
132! flag to set/remove calls to groupeun
133      logical callgroupeun
134      parameter (callgroupeun = .false.)
135c-----------------------------------------------------------------------
136c   Initialisations:
137c   ----------------
138
139      modname = 'gcm'
140      descript = 'Run GCM LMDZ'
141      lafin    = .FALSE.
142
143c-----------------------------------------------------------------------
144c  Initialize tracers using iniadvtrac (Ehouarn, oct 2008)
145      CALL iniadvtrac(nq,numvanle)
146
147      CALL dynetat0("start.nc",nqmx,vcov,ucov,
148     .              teta,q,masse,ps,phis, time_0)
149
150      CALL defrun_new( 99, .TRUE. )
151      ! in case time_0 (because of roundoffs) is close to zero,
152      ! set it to zero to avoid roundoff propagation issues
153      if ((time_0.gt.0.).and.(time_0.lt.(1./day_step))) then
154        write(*,*)"GCM: In start.nc, time=",time_0
155        write(*,*)"     but day_step=",day_step
156        write(*,*)"     and 1./day_step=",1./day_step
157        write(*,*)"     fix this drift by setting time=0"
158        time_0=0.
159      endif
160
161
162c  on recalcule eventuellement le pas de temps
163
164      IF(MOD(day_step,iperiod).NE.0)
165     * STOP'Il faut choisir un nb de pas par jour multiple de iperiod'
166
167      IF(MOD(day_step,iphysiq).NE.0)
168     * STOP'Il faut choisir un nb de pas par jour multiple de iphysiq'
169
170      zdtvr    = daysec/REAL(day_step)
171        IF(dtvr.NE.zdtvr) THEN
172         PRINT*,'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
173        ENDIF
174
175c  nombre d'etats dans les fichiers demarrage et histoire
176
177      dtvr = zdtvr
178      CALL iniconst
179      CALL inigeom
180
181      CALL inifilr
182
183c
184c   ......    P.Le Van    ( modif  le 29/04/97 )   ......... 
185c
186
187      CALL inidissip ( lstardis, nitergdiv, nitergrot, niterh   ,
188     *                tetagdiv, tetagrot , tetatemp              )
189c
190
191
192      call dump2d(iip1,jjp1,ps,'PRESSION SURFACE')
193
194c
195c  numero de stockage pour les fichiers de redemarrage:
196
197c-----------------------------------------------------------------------
198c   temps de depart et de fin:
199c   --------------------------
200
201      itau = 0
202      iday = day_ini+itau/day_step
203      time = REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
204         IF(time.GT.1.) THEN
205          time = time-1.
206          iday = iday+1
207         ENDIF
208      if (ndynstep .gt. 0) then
209         itaufin = ndynstep
210      else
211         itaufin=nint(nday_r*day_step) ! nint() to avoid problematic roundoffs
212      endif
213      ! check that this is compatible with call sequence dyn/phys/dissip
214      ! i.e. that itaufin is a multiple of iphysiq and idissip
215      if ((modulo(itaufin,iphysiq).ne.0).or.
216     &    (modulo(itaufin,idissip).ne.0)) then
217        if (ndynstep .gt. 0) then
218       write(*,'(A,I5)')
219     &  "gcm: Problem: incompatibility between ndynstep=",ndynstep
220        else
221       write(*,'((A,F9.2),2(A,I5))')
222     &  "gcm: Problem: incompatibility between nday=",nday_r,
223     &  " day_step=",day_step," which imply itaufin=",itaufin
224        endif
225        write(*,'(2(A,I5))')
226     &   "  whereas iphysiq=",iphysiq," and idissip=",
227     &  idissip
228        stop
229      endif
230!      write(*,*)"gcm: itaufin=",itaufin
231c ********************************
232c      itaufin = 120   ! temporaire !!
233c ********************************
234      itaufinp1 = itaufin +1
235
236      if (ndynstep .gt. 0) then
237        day_end = day_ini
238     &          + floor(float(ndynstep)/float(day_step)+time_0)
239      else
240        day_end = day_ini + floor(nday_r+time_0)
241      endif
242      PRINT 300, itau,itaufin,day_ini,day_end
243 300  FORMAT('1'/,15x,'run du pas',i7,2x,'au pas',i7,2x, 
244     . 'c''est a dire du jour',i7,3x,'au jour',i7//)
245
246      CALL dynredem0("restart.nc",day_end,anne_ini,phis,nqmx)
247
248      ecripar = .TRUE.
249
250      dtav = iperiod*dtvr/daysec
251
252
253c   Quelques initialisations pour les traceurs
254      call initial0(ijp1llm*nqmx,dq)
255c     istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
256c     istphy=istdyn/iphysiq
257
258      write(*,*) "gcm: callgroupeun set to:",callgroupeun
259c-----------------------------------------------------------------------
260c   Debut de l'integration temporelle:
261c   ----------------------------------
262
263   1  CONTINUE
264c
265c TN 09/2012. To ensure "1+1=2" in dynamical core :
266c update atmospheric pressure IN the main loop
267      CALL pression ( ip1jmp1, ap, bp, ps, p       )
268      CALL exner_hyb( ip1jmp1, ps, p,beta, pks, pk, pkf )
269
270      IF( MOD( itau, 10* day_step ).EQ.0 )  THEN
271        CALL test_period ( ucov,vcov,teta,q,p,phis )
272        write(*,*)' GCM ---- Test_period apres continue   OK ! -----',
273     &            ' itau: ',itau
274      ENDIF
275
276      if (callgroupeun) then
277        call groupeun(jjp1,llm,ucov,.true.)
278        call groupeun(jjm,llm,vcov,.true.)
279        call groupeun(jjp1,llm,teta,.true.)
280        call groupeun(jjp1,llm,masse,.true.)
281        call groupeun(jjp1,1,ps,.false.)
282      endif
283
284      CALL SCOPY( ijmllm ,vcov , 1, vcovm1 , 1 )
285      CALL SCOPY( ijp1llm,ucov , 1, ucovm1 , 1 )
286      CALL SCOPY( ijp1llm,teta , 1, tetam1 , 1 )
287      CALL SCOPY( ijp1llm,masse, 1, massem1, 1 )
288      CALL SCOPY( ip1jmp1, ps  , 1,   psm1 , 1 )
289
290      forward = .TRUE.
291      leapf   = .FALSE.
292      dt      =  dtvr
293
294c   ...    P.Le Van .26/04/94  ....
295
296      CALL SCOPY   ( ijp1llm,   masse, 1, finvmaold,     1 )
297      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
298
299
300   2  CONTINUE
301
302c-----------------------------------------------------------------------
303
304c   date:
305c   -----
306
307!      write(*,*) 'GCM: itau=',itau
308
309c   gestion des appels de la physique et des dissipations:
310c   ------------------------------------------------------
311c
312c   ...    P.Le Van  ( 6/02/95 )  ....
313
314      apphys = .FALSE.
315      statcl = .FALSE.
316      conser = .FALSE.
317      apdiss = .FALSE.
318
319      IF( purmats ) THEN
320         IF( MOD(itau,iconser) .EQ.0.AND.  forward    ) conser = .TRUE.
321         IF( MOD(itau,idissip ).EQ.0.AND..NOT.forward ) apdiss = .TRUE.
322         IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward
323     $                              .AND.   physic    ) apphys = .TRUE.
324      ELSE
325         IF( MOD(itau   ,iconser) .EQ. 0              ) conser = .TRUE.
326         IF( MOD(itau+1,idissip)  .EQ. 0              ) apdiss = .TRUE.
327         IF( MOD(itau+1,iphysiq).EQ.0. AND. physic    ) apphys = .TRUE.
328      END IF
329
330c-----------------------------------------------------------------------
331c   calcul des tendances dynamiques:
332c   --------------------------------
333
334      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
335c
336c
337      CALL caldyn
338     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
339     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time+iday-day_ini )
340
341
342c-----------------------------------------------------------------------
343c   calcul des tendances advection des traceurs (dont l'humidite)
344c   -------------------------------------------------------------
345
346      if (tracer) then
347       IF( forward. OR . leapf )  THEN
348
349        DO iq = 1, nqmx
350c
351         IF ( iadv(iq).EQ.1.OR.iadv(iq).EQ.2 )  THEN
352            CALL traceur( iq,iadv,q,teta,pk,w, pbaru, pbarv, dq )
353
354         ELSE IF( iq.EQ. nqmx )   THEN
355c
356            iapp_tracvl = 5
357c
358cccc     iapp_tracvl est la frequence en pas du groupement des flux
359cccc      de masse pour  Van-Leer dans la routine  tracvl  .
360c
361
362            CALL vanleer(numvanle,iapp_tracvl,nqmx,q,pbaru,pbarv,
363     *                      p, masse, dq,  iadv(1), teta, pk     )
364
365c
366c                   ...  Modif  F.Codron  ....
367c
368         ENDIF
369c
370        ENDDO
371C
372c        IF (offline) THEN
373C maf stokage du flux de masse pour traceurs OFF-LINE
374
375c           CALL fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
376c    .   time_step, itau)
377
378c        ENDIF
379c
380      ENDIF
381          END IF   ! tracer
382
383
384c-----------------------------------------------------------------------
385c   integrations dynamique et traceurs:
386c   ----------------------------------
387
388       CALL integrd ( 2,vcovm1,ucovm1,tetam1,psm1,massem1 ,
389     $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,
390     $              finvmaold )
391
392c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
393c
394c-----------------------------------------------------------------------
395c   calcul des tendances physiques:
396c   -------------------------------
397c    ########   P.Le Van ( Modif le  6/02/95 )   ###########
398c
399       IF( purmats )  THEN
400          IF( itau.EQ.itaufin.AND..NOT.forward ) lafin = .TRUE.
401       ELSE
402          IF( itau+1. EQ. itaufin )              lafin = .TRUE.
403       ENDIF
404c
405c
406       IF( apphys )  THEN
407c
408c     .......   Ajout   P.Le Van ( 17/04/96 )   ...........
409c
410
411         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
412         CALL exner_hyb(  ip1jmp1, ps, p,beta,pks, pk, pkf )
413
414           rdaym_ini  = itau * dtvr / daysec + time_0
415           rdayvrai   = rdaym_ini  + day_ini
416
417           IF ( ecritphy.LT.1. )  THEN
418             rday_ecri = rdaym_ini
419           ELSE
420             rday_ecri = INT( rdayvrai )
421           ENDIF
422c
423        CALL calfis( nqmx, lafin ,rdayvrai,rday_ecri,time  ,
424     $                 ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
425     $     du,dv,dteta,dq,w, dufi,dvfi,dhfi,dqfi,dpfi,tracer)
426
427
428c      ajout des tendances physiques:
429c      ------------------------------
430          CALL addfi( nqmx, dtphys, leapf, forward   ,
431     $                  ucov, vcov, teta , q   ,ps , masse,
432     $                 dufi, dvfi, dhfi , dqfi ,dpfi  )
433c
434       ENDIF
435
436       CALL pression ( ip1jmp1, ap, bp, ps, p                  )
437
438       CALL exner_hyb( ip1jmp1, ps, p,beta, pks, pk, pkf )
439c   ----------------------------------------------------------
440
441c
442c
443c   dissipation horizontale et verticale  des petites echelles:
444c   ----------------------------------------------------------
445
446
447      IF(apdiss) THEN
448
449c        Sponge layer
450c        ~~~~~~~~~~~~
451         DO ij=1, ip1jmp1
452            pext(ij)=ps(ij)*aire(ij)
453         ENDDO
454         IF (callsponge) THEN
455            CALL sponge(ucov,vcov,teta,pext,dtdiss,mode_sponge)
456         ENDIF
457
458c        Dissipation horizontale
459c        ~~~~~~~~~~~~~~~~~~~~~~~
460         CALL dissip(vcov,ucov,teta,p,dvdis,dudis,dhdis)
461
462         CALL addit( ijp1llm,ucov ,dudis,ucov )
463         CALL addit( ijmllm ,vcov ,dvdis,vcov )
464         CALL addit( ijp1llm,teta ,dhdis,teta )
465
466
467c    .......        P. Le Van (  ajout  le 17/04/96  )   ...........
468c   ...      Calcul de la valeur moyenne, unique de h aux poles  .....
469c
470
471        DO l  =  1, llm
472          DO ij =  1,iim
473           tppn(ij)  = aire(  ij    ) * teta(  ij    ,l)
474           tpps(ij)  = aire(ij+ip1jm) * teta(ij+ip1jm,l)
475          ENDDO
476
477           tpn  = SSUM(iim,tppn,1)/apoln
478           tps  = SSUM(iim,tpps,1)/apols
479
480          DO ij = 1, iip1
481           teta(  ij    ,l) = tpn
482           teta(ij+ip1jm,l) = tps
483          ENDDO
484        ENDDO
485
486        DO ij =  1,iim
487          tppn(ij)  = aire(  ij    ) * ps (  ij    )
488          tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
489        ENDDO
490          tpn  = SSUM(iim,tppn,1)/apoln
491
492          tps  = SSUM(iim,tpps,1)/apols
493
494        DO ij = 1, iip1
495          ps(  ij    ) = tpn
496          ps(ij+ip1jm) = tps
497        ENDDO
498
499
500      END IF
501       
502c   ********************************************************************
503c   ********************************************************************
504c   .... fin de l'integration dynamique  et physique pour le pas itau ..
505c   ********************************************************************
506c   ********************************************************************
507
508c   preparation du pas d'integration suivant  ......
509
510      IF ( .NOT.purmats ) THEN
511c       ........................................................
512c       ..............  schema matsuno + leapfrog  ..............
513c       ........................................................
514
515            IF(forward. OR. leapf) THEN
516              itau= itau + 1
517              iday= day_ini+itau/day_step
518              time= REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
519                IF(time.GT.1.) THEN
520                  time = time-1.
521                  iday = iday+1
522                ENDIF
523            ENDIF
524
525
526            IF( itau. EQ. itaufinp1 ) then 
527              abort_message = 'Simulation finished'
528              call abort_gcm(modname,abort_message,0)
529            ENDIF
530c-----------------------------------------------------------------------
531c   ecriture du fichier histoire moyenne:
532c   -------------------------------------
533
534c           IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
535c              IF(itau.EQ.itaufin) THEN
536c                 iav=1
537c              ELSE
538c                 iav=0
539c              ENDIF
540c              CALL writedynav(histaveid, nqmx, itau,vcov ,
541c    ,                          ucov,teta,pk,phi,q,masse,ps,phis)
542c           ENDIF
543
544c-----------------------------------------------------------------------
545
546
547            IF(itau.EQ.itaufin) THEN
548
549
550       write(*,*)' GCM: Appel test_period avant redem ; itau=',itau
551       CALL test_period ( ucov,vcov,teta,q,p,phis )
552       CALL dynredem1("restart.nc",time,
553     .                     vcov,ucov,teta,q,nqmx,masse,ps)
554
555              CLOSE(99)
556            ENDIF
557
558c-----------------------------------------------------------------------
559c   gestion de l'integration temporelle:
560c   ------------------------------------
561
562            IF( MOD(itau,iperiod).EQ.0 )    THEN
563                    GO TO 1
564            ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
565
566                   IF( forward )  THEN
567c      fin du pas forward et debut du pas backward
568
569                      forward = .FALSE.
570                        leapf = .FALSE.
571                           GO TO 2
572
573                   ELSE
574c      fin du pas backward et debut du premier pas leapfrog
575
576                        leapf =  .TRUE.
577                        dt  =  2.*dtvr
578                        GO TO 2
579                   END IF
580            ELSE
581
582c      ......   pas leapfrog  .....
583
584                 leapf = .TRUE.
585                 dt  = 2.*dtvr
586                 GO TO 2
587            END IF
588
589      ELSE
590
591c       ........................................................
592c       ..............       schema  matsuno        ...............
593c       ........................................................
594            IF( forward )  THEN
595
596             itau =  itau + 1
597             iday = day_ini+itau/day_step
598             time = REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
599
600                  IF(time.GT.1.) THEN
601                   time = time-1.
602                   iday = iday+1
603                  ENDIF
604
605               forward =  .FALSE.
606               IF( itau. EQ. itaufinp1 ) then 
607                 abort_message = 'Simulation finished'
608                 call abort_gcm(modname,abort_message,0)
609               ENDIF
610               GO TO 2
611
612            ELSE
613
614            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
615               IF(itau.EQ.itaufin) THEN
616                  iav=1
617               ELSE
618                  iav=0
619               ENDIF
620c              CALL writedynav(histaveid, nqmx, itau,vcov ,
621c    ,                          ucov,teta,pk,phi,q,masse,ps,phis)
622
623            ENDIF
624
625
626                 IF(itau.EQ.itaufin)
627     . CALL dynredem1("restart.nc",time,
628     .                     vcov,ucov,teta,q,nqmx,masse,ps)
629
630                 forward = .TRUE.
631                 GO TO  1
632
633
634            ENDIF
635
636      END IF
637
638      STOP
639      END
Note: See TracBrowser for help on using the repository browser.