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

Last change on this file since 999 was 999, checked in by tnavarro, 11 years ago

Possibility to store multiple initial states in one start/startfi. This is RETROCOMPATIBLE. New option ecrithist in run.def to write data in start/startfi every ecrithist dynamical timestep. New option timestart in run.def to initialize the GCM with the time timestart stored in start

File size: 19.3 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 defrun_new( 99, .TRUE. )
146
147      CALL iniadvtrac(nq,numvanle)
148     
149      CALL dynetat0("start.nc",nqmx,vcov,ucov,
150     .              teta,q,masse,ps,phis,time_0)
151
152      ! in case time_0 (because of roundoffs) is close to zero,
153      ! set it to zero to avoid roundoff propagation issues
154      if ((time_0.gt.0.).and.(time_0.lt.(1./day_step))) then
155        write(*,*)"GCM: In start.nc, time=",time_0
156        write(*,*)"     but day_step=",day_step
157        write(*,*)"     and 1./day_step=",1./day_step
158        write(*,*)"     fix this drift by setting time=0"
159        time_0=0.
160      endif
161
162
163c  on recalcule eventuellement le pas de temps
164
165      IF(MOD(day_step,iperiod).NE.0)
166     * STOP'Il faut choisir un nb de pas par jour multiple de iperiod'
167
168      IF(MOD(day_step,iphysiq).NE.0)
169     * STOP'Il faut choisir un nb de pas par jour multiple de iphysiq'
170
171      zdtvr    = daysec/REAL(day_step)
172        IF(dtvr.NE.zdtvr) THEN
173         PRINT*,'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
174        ENDIF
175
176c  nombre d'etats dans les fichiers demarrage et histoire
177
178      dtvr = zdtvr
179      CALL iniconst
180      CALL inigeom
181
182      CALL inifilr
183
184c
185c   ......    P.Le Van    ( modif  le 29/04/97 )   ......... 
186c
187
188      CALL inidissip ( lstardis, nitergdiv, nitergrot, niterh   ,
189     *                tetagdiv, tetagrot , tetatemp              )
190c
191
192
193      call dump2d(iip1,jjp1,ps,'PRESSION SURFACE')
194
195c
196c  numero de stockage pour les fichiers de redemarrage:
197
198c-----------------------------------------------------------------------
199c   temps de depart et de fin:
200c   --------------------------
201
202      itau = 0
203      iday = day_ini+itau/day_step
204      time = REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
205         IF(time.GT.1.) THEN
206          time = time-1.
207          iday = iday+1
208         ENDIF
209      if (ndynstep .gt. 0) then
210         itaufin = ndynstep
211      else
212         itaufin=nint(nday_r*day_step) ! nint() to avoid problematic roundoffs
213      endif
214      ! check that this is compatible with call sequence dyn/phys/dissip
215      ! i.e. that itaufin is a multiple of iphysiq and idissip
216      if ((modulo(itaufin,iphysiq).ne.0).or.
217     &    (modulo(itaufin,idissip).ne.0)) then
218        if (ndynstep .gt. 0) then
219       write(*,'(A,I5)')
220     &  "gcm: Problem: incompatibility between ndynstep=",ndynstep
221        else
222       write(*,'((A,F9.2),2(A,I5))')
223     &  "gcm: Problem: incompatibility between nday=",nday_r,
224     &  " day_step=",day_step," which imply itaufin=",itaufin
225        endif
226        write(*,'(2(A,I5))')
227     &   "  whereas iphysiq=",iphysiq," and idissip=",
228     &  idissip
229        stop
230      endif
231!      write(*,*)"gcm: itaufin=",itaufin
232c ********************************
233c      itaufin = 120   ! temporaire !!
234c ********************************
235      itaufinp1 = itaufin +1
236
237      if (ndynstep .gt. 0) then
238        day_end = day_ini
239     &          + floor(float(ndynstep)/float(day_step)+time_0)
240      else
241        day_end = day_ini + floor(nday_r+time_0)
242      endif
243      PRINT 300, itau,itaufin,day_ini,day_end
244 300  FORMAT('1'/,15x,'run du pas',i7,2x,'au pas',i7,2x, 
245     . 'c''est a dire du jour',i7,3x,'au jour',i7//)
246
247      CALL dynredem0("restart.nc",day_ini,anne_ini,phis,nqmx)
248
249      ecripar = .TRUE.
250
251      dtav = iperiod*dtvr/daysec
252
253
254c   Quelques initialisations pour les traceurs
255      call initial0(ijp1llm*nqmx,dq)
256c     istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
257c     istphy=istdyn/iphysiq
258
259      write(*,*) "gcm: callgroupeun set to:",callgroupeun
260c-----------------------------------------------------------------------
261c   Debut de l'integration temporelle:
262c   ----------------------------------
263
264   1  CONTINUE
265c
266c TN 09/2012. To ensure "1+1=2" in dynamical core :
267c update atmospheric pressure IN the main loop
268      CALL pression ( ip1jmp1, ap, bp, ps, p       )
269      CALL exner_hyb( ip1jmp1, ps, p,beta, pks, pk, pkf )
270
271      IF( MOD( itau, 10* day_step ).EQ.0 )  THEN
272        CALL test_period ( ucov,vcov,teta,q,p,phis )
273        write(*,*)' GCM ---- Test_period apres continue   OK ! -----',
274     &            ' itau: ',itau
275      ENDIF
276
277      if (callgroupeun) then
278        call groupeun(jjp1,llm,ucov,.true.)
279        call groupeun(jjm,llm,vcov,.true.)
280        call groupeun(jjp1,llm,teta,.true.)
281        call groupeun(jjp1,llm,masse,.true.)
282        call groupeun(jjp1,1,ps,.false.)
283      endif
284
285      CALL SCOPY( ijmllm ,vcov , 1, vcovm1 , 1 )
286      CALL SCOPY( ijp1llm,ucov , 1, ucovm1 , 1 )
287      CALL SCOPY( ijp1llm,teta , 1, tetam1 , 1 )
288      CALL SCOPY( ijp1llm,masse, 1, massem1, 1 )
289      CALL SCOPY( ip1jmp1, ps  , 1,   psm1 , 1 )
290
291      forward = .TRUE.
292      leapf   = .FALSE.
293      dt      =  dtvr
294
295c   ...    P.Le Van .26/04/94  ....
296
297      CALL SCOPY   ( ijp1llm,   masse, 1, finvmaold,     1 )
298      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
299
300
301   2  CONTINUE
302
303c-----------------------------------------------------------------------
304
305c   date:
306c   -----
307
308!      write(*,*) 'GCM: itau=',itau
309
310c   gestion des appels de la physique et des dissipations:
311c   ------------------------------------------------------
312c
313c   ...    P.Le Van  ( 6/02/95 )  ....
314
315      apphys = .FALSE.
316      statcl = .FALSE.
317      conser = .FALSE.
318      apdiss = .FALSE.
319
320      IF( purmats ) THEN
321         IF( MOD(itau,iconser) .EQ.0.AND.  forward    ) conser = .TRUE.
322         IF( MOD(itau,idissip ).EQ.0.AND..NOT.forward ) apdiss = .TRUE.
323         IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward
324     $                              .AND.   physic    ) apphys = .TRUE.
325      ELSE
326         IF( MOD(itau   ,iconser) .EQ. 0              ) conser = .TRUE.
327         IF( MOD(itau+1,idissip)  .EQ. 0              ) apdiss = .TRUE.
328         IF( MOD(itau+1,iphysiq).EQ.0. AND. physic    ) apphys = .TRUE.
329      END IF
330
331c-----------------------------------------------------------------------
332c   calcul des tendances dynamiques:
333c   --------------------------------
334
335      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
336c
337c
338      CALL caldyn
339     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
340     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time+iday-day_ini )
341
342
343c-----------------------------------------------------------------------
344c   calcul des tendances advection des traceurs (dont l'humidite)
345c   -------------------------------------------------------------
346
347      if (tracer) then
348       IF( forward. OR . leapf )  THEN
349
350        DO iq = 1, nqmx
351c
352         IF ( iadv(iq).EQ.1.OR.iadv(iq).EQ.2 )  THEN
353            CALL traceur( iq,iadv,q,teta,pk,w, pbaru, pbarv, dq )
354
355         ELSE IF( iq.EQ. nqmx )   THEN
356c
357            iapp_tracvl = 5
358c
359cccc     iapp_tracvl est la frequence en pas du groupement des flux
360cccc      de masse pour  Van-Leer dans la routine  tracvl  .
361c
362
363            CALL vanleer(numvanle,iapp_tracvl,nqmx,q,pbaru,pbarv,
364     *                      p, masse, dq,  iadv(1), teta, pk     )
365
366c
367c                   ...  Modif  F.Codron  ....
368c
369         ENDIF
370c
371        ENDDO
372C
373c        IF (offline) THEN
374C maf stokage du flux de masse pour traceurs OFF-LINE
375
376c           CALL fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
377c    .   time_step, itau)
378
379c        ENDIF
380c
381      ENDIF
382          END IF   ! tracer
383
384
385c-----------------------------------------------------------------------
386c   integrations dynamique et traceurs:
387c   ----------------------------------
388
389       CALL integrd ( 2,vcovm1,ucovm1,tetam1,psm1,massem1 ,
390     $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,
391     $              finvmaold )
392
393c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
394c
395c-----------------------------------------------------------------------
396c   calcul des tendances physiques:
397c   -------------------------------
398c    ########   P.Le Van ( Modif le  6/02/95 )   ###########
399c
400       IF( purmats )  THEN
401          IF( itau.EQ.itaufin.AND..NOT.forward ) lafin = .TRUE.
402       ELSE
403          IF( itau+1. EQ. itaufin )              lafin = .TRUE.
404       ENDIF
405c
406c
407       IF( apphys )  THEN
408c
409c     .......   Ajout   P.Le Van ( 17/04/96 )   ...........
410c
411
412         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
413         CALL exner_hyb(  ip1jmp1, ps, p,beta,pks, pk, pkf )
414
415           rdaym_ini  = itau * dtvr / daysec + time_0
416           rdayvrai   = rdaym_ini  + day_ini
417
418           IF ( ecritphy.LT.1. )  THEN
419             rday_ecri = rdaym_ini
420           ELSE
421             rday_ecri = INT( rdayvrai )
422           ENDIF
423c
424        CALL calfis( nqmx, lafin ,rdayvrai,rday_ecri,time  ,
425     $                 ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
426     $     du,dv,dteta,dq,w, dufi,dvfi,dhfi,dqfi,dpfi,tracer)
427
428
429c      ajout des tendances physiques:
430c      ------------------------------
431          CALL addfi( nqmx, dtphys, leapf, forward   ,
432     $                  ucov, vcov, teta , q   ,ps , masse,
433     $                 dufi, dvfi, dhfi , dqfi ,dpfi  )
434c
435       ENDIF
436
437       CALL pression ( ip1jmp1, ap, bp, ps, p                  )
438
439       CALL exner_hyb( ip1jmp1, ps, p,beta, pks, pk, pkf )
440c   ----------------------------------------------------------
441
442c
443c
444c   dissipation horizontale et verticale  des petites echelles:
445c   ----------------------------------------------------------
446
447
448      IF(apdiss) THEN
449
450c        Sponge layer
451c        ~~~~~~~~~~~~
452         DO ij=1, ip1jmp1
453            pext(ij)=ps(ij)*aire(ij)
454         ENDDO
455         IF (callsponge) THEN
456            CALL sponge(ucov,vcov,teta,pext,dtdiss,mode_sponge)
457         ENDIF
458
459c        Dissipation horizontale
460c        ~~~~~~~~~~~~~~~~~~~~~~~
461         CALL dissip(vcov,ucov,teta,p,dvdis,dudis,dhdis)
462
463         CALL addit( ijp1llm,ucov ,dudis,ucov )
464         CALL addit( ijmllm ,vcov ,dvdis,vcov )
465         CALL addit( ijp1llm,teta ,dhdis,teta )
466
467
468c    .......        P. Le Van (  ajout  le 17/04/96  )   ...........
469c   ...      Calcul de la valeur moyenne, unique de h aux poles  .....
470c
471
472        DO l  =  1, llm
473          DO ij =  1,iim
474           tppn(ij)  = aire(  ij    ) * teta(  ij    ,l)
475           tpps(ij)  = aire(ij+ip1jm) * teta(ij+ip1jm,l)
476          ENDDO
477
478           tpn  = SSUM(iim,tppn,1)/apoln
479           tps  = SSUM(iim,tpps,1)/apols
480
481          DO ij = 1, iip1
482           teta(  ij    ,l) = tpn
483           teta(ij+ip1jm,l) = tps
484          ENDDO
485        ENDDO
486
487        DO ij =  1,iim
488          tppn(ij)  = aire(  ij    ) * ps (  ij    )
489          tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
490        ENDDO
491          tpn  = SSUM(iim,tppn,1)/apoln
492
493          tps  = SSUM(iim,tpps,1)/apols
494
495        DO ij = 1, iip1
496          ps(  ij    ) = tpn
497          ps(ij+ip1jm) = tps
498        ENDDO
499
500
501      END IF
502       
503c   ********************************************************************
504c   ********************************************************************
505c   .... fin de l'integration dynamique  et physique pour le pas itau ..
506c   ********************************************************************
507c   ********************************************************************
508
509c   preparation du pas d'integration suivant  ......
510
511      IF ( .NOT.purmats ) THEN
512c       ........................................................
513c       ..............  schema matsuno + leapfrog  ..............
514c       ........................................................
515
516            IF(forward. OR. leapf) THEN
517              itau= itau + 1
518              iday= day_ini+itau/day_step
519              time= REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
520                !IF(time.GT.1.) THEN
521                IF(time.GE.1.) THEN
522                  time = time-1.
523                  iday = iday+1
524                ENDIF
525            ENDIF
526
527
528            IF( itau. EQ. itaufinp1 ) then 
529              abort_message = 'Simulation finished'
530              call abort_gcm(modname,abort_message,0)
531            ENDIF
532c-----------------------------------------------------------------------
533c   ecriture du fichier histoire moyenne:
534c   -------------------------------------
535
536c           IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
537c              IF(itau.EQ.itaufin) THEN
538c                 iav=1
539c              ELSE
540c                 iav=0
541c              ENDIF
542c              CALL writedynav(histaveid, nqmx, itau,vcov ,
543c    ,                          ucov,teta,pk,phi,q,masse,ps,phis)
544c           ENDIF
545
546c-----------------------------------------------------------------------
547
548            IF( (ecritstart.GT.0) .and. (MOD(itau,ecritstart).EQ.0)
549     .        .or. (itau.EQ.itaufin) ) THEN
550           
551       !write(*,*)' GCM: Appel test_period avant redem ; itau=',itau
552       CALL test_period ( ucov,vcov,teta,q,p,phis )
553       
554       write(*,'(A,I7,A,F12.5)')
555     .  'GCM:    Ecriture du fichier restart   ; itau=  ',itau,
556     .  ' date=',REAL(itau)/REAL(day_step)
557       CALL dynredem1("restart.nc",REAL(itau)/REAL(day_step),
558     .                vcov,ucov,teta,q,nqmx,masse,ps)
559     
560      CLOSE(99)
561     
562            ENDIF
563
564
565c-----------------------------------------------------------------------
566c   gestion de l'integration temporelle:
567c   ------------------------------------
568
569            IF( MOD(itau,iperiod).EQ.0 )    THEN
570                    GO TO 1
571            ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
572
573                   IF( forward )  THEN
574c      fin du pas forward et debut du pas backward
575
576                      forward = .FALSE.
577                        leapf = .FALSE.
578                           GO TO 2
579
580                   ELSE
581c      fin du pas backward et debut du premier pas leapfrog
582
583                        leapf =  .TRUE.
584                        dt  =  2.*dtvr
585                        GO TO 2
586                   END IF
587            ELSE
588
589c      ......   pas leapfrog  .....
590
591                 leapf = .TRUE.
592                 dt  = 2.*dtvr
593                 GO TO 2
594            END IF
595
596      ELSE
597
598c       ........................................................
599c       ..............       schema  matsuno        ...............
600c       ........................................................
601            IF( forward )  THEN
602
603             itau =  itau + 1
604             iday = day_ini+itau/day_step
605             time = REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
606
607                  IF(time.GE.1.) THEN
608                   time = time-1.
609                   iday = iday+1
610                  ENDIF
611
612               forward =  .FALSE.
613               IF( itau. EQ. itaufinp1 ) then 
614                 abort_message = 'Simulation finished'
615                 call abort_gcm(modname,abort_message,0)
616               ENDIF
617               GO TO 2
618
619            ELSE
620
621            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
622               IF(itau.EQ.itaufin) THEN
623                  iav=1
624               ELSE
625                  iav=0
626               ENDIF
627c              CALL writedynav(histaveid, nqmx, itau,vcov ,
628c    ,                          ucov,teta,pk,phi,q,masse,ps,phis)
629
630            ENDIF
631
632
633            IF( (ecritstart.GT.0) .and. (MOD(itau,ecritstart).EQ.0)
634     .      .or. (itau.EQ.itaufin) ) THEN
635           
636              CALL dynredem1("restart.nc",
637     .                REAL(itau)/REAL(day_step),
638     .                vcov,ucov,teta,q,nqmx,masse,ps)
639     
640              forward = .TRUE.
641              GO TO  1
642             
643            ENDIF
644
645
646            ENDIF
647
648      END IF
649
650      STOP
651      END
Note: See TracBrowser for help on using the repository browser.