source: trunk/LMDZ.PLUTO.old/libf/dyn3d/gcm.F_new @ 3436

Last change on this file since 3436 was 3175, checked in by emillour, 11 months ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

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