source: trunk/LMDZ.GENERIC/libf/dyn3d/gcm.F @ 773

Last change on this file since 773 was 649, checked in by jleconte, 13 years ago
  • Correction a huge bug in newstart: rcp and cpp can now be changed in start.nc files and are the same as in startfi.nc;

Even when starting from start and startfi files.

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