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

Last change on this file since 317 was 38, checked in by emillour, 14 years ago

Ajout du modè Martien (mon LMDZ.MARS.BETA, du 28/01/2011) dans le rértoire mars, pour pouvoir suivre plus facilement les modifs.
EM

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