source: LMDZ.3.3/branches/rel-LF/libf/dyn3d/gcm.F @ 474

Last change on this file since 474 was 474, checked in by lmdzadmin, 21 years ago

Pour la remise a zero de l'origine du calendrier de la simulation
LF

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 24.3 KB
Line 
1
2      PROGRAM gcm
3
4      USE IOIPSL
5
6      IMPLICIT NONE
7
8c      ......   Version  du 10/01/98    ..........
9
10c             avec  coordonnees  verticales hybrides
11c   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
12
13c=======================================================================
14c
15c   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
16c   -------
17c
18c   Objet:
19c   ------
20c
21c   GCM LMD nouvelle grille
22c
23c=======================================================================
24c
25c  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
26c      et possibilite d'appeler une fonction f(y)  a derivee tangente
27c      hyperbolique a la  place de la fonction a derivee sinusoidale.
28
29c  ... Possibilite de choisir le shema de Van-leer pour l'advection de
30c        q  , en faisant iadv = 3  dans   traceur  (29/04/97) .
31c
32c      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
33c
34c-----------------------------------------------------------------------
35c   Declarations:
36c   -------------
37
38#include "dimensions.h"
39#include "paramet.h"
40#include "comconst.h"
41#include "comdissnew.h"
42#include "comvert.h"
43#include "comgeom.h"
44#include "logic.h"
45#include "temps.h"
46#include "control.h"
47#include "ener.h"
48#include "netcdf.inc"
49#include "description.h"
50#include "serre.h"
51#include "tracstoke.h"
52
53
54      INTEGER         longcles
55      PARAMETER     ( longcles = 20 )
56      REAL  clesphy0( longcles )
57      SAVE  clesphy0
58
59      INTEGER*4  iday ! jour julien
60      REAL       time ! Heure de la journee en fraction d'1 jour
61      REAL zdtvr
62      INTEGER nbetatmoy, nbetatdem,nbetat
63
64c   variables dynamiques
65      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
66      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
67      REAL q(ip1jmp1,llm,nqmx)               ! champs advectes
68      REAL ps(ip1jmp1)                       ! pression  au sol
69      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
70      REAL pks(ip1jmp1)                      ! exner au  sol
71      REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
72      REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
73      REAL masse(ip1jmp1,llm)                ! masse d'air
74      REAL phis(ip1jmp1)                     ! geopotentiel au sol
75      REAL phi(ip1jmp1,llm)                  ! geopotentiel
76      REAL w(ip1jmp1,llm)                    ! vitesse verticale
77
78c variables dynamiques intermediaire pour le transport
79      REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm) !flux de masse
80
81c   variables dynamiques au pas -1
82      REAL vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm)
83      REAL tetam1(ip1jmp1,llm),psm1(ip1jmp1)
84      REAL massem1(ip1jmp1,llm)
85
86c   tendances dynamiques
87      REAL dv(ip1jm,llm),du(ip1jmp1,llm)
88      REAL dteta(ip1jmp1,llm),dq(ip1jmp1,llm,nqmx),dp(ip1jmp1)
89
90c   tendances de la dissipation
91      REAL dvdis(ip1jm,llm),dudis(ip1jmp1,llm)
92      REAL dhdis(ip1jmp1,llm)
93
94c   tendances physiques
95      REAL dvfi(ip1jm,llm),dufi(ip1jmp1,llm)
96      REAL dhfi(ip1jmp1,llm),dqfi(ip1jmp1,llm,nqmx),dpfi(ip1jmp1)
97
98c   variables pour le fichier histoire
99      REAL dtav      ! intervalle de temps elementaire
100
101      REAL tppn(iim),tpps(iim),tpn,tps
102c
103      INTEGER iadv(nqmx) ! indice schema de transport pour le traceur iq
104
105      INTEGER itau,itaufinp1,iav
106
107      EXTERNAL caldyn, traceur
108      EXTERNAL dissip,geopot,iniconst,inifilr
109      EXTERNAL integrd,SCOPY
110      EXTERNAL iniav,writeav,writehist
111      EXTERNAL inigeom
112      EXTERNAL exner_hyb,addit
113      EXTERNAL defrun_new, test_period
114      REAL  SSUM
115      REAL time_0 , finvmaold(ip1jmp1,llm)
116
117      LOGICAL lafin
118      INTEGER ij,iq,l,numvanle,iapp_tracvl
119
120
121      INTEGER fluxid, fluxvid,fluxdid
122      integer histid, histvid, histaveid
123      real time_step, t_wrt, t_ops
124
125      REAL rdayvrai,rdaym_ini,rday_ecri
126      LOGICAL first
127      REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm)
128c+jld variables test conservation energie
129      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
130C     Tendance de la temp. potentiel d (theta)/ d t due a la
131C     tansformation d'energie cinetique en energie thermique
132C     cree par la dissipation
133      REAL dhecdt(ip1jmp1,llm)
134      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
135      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
136      CHARACTER*15 ztit
137      INTEGER   ip_ebil_dyn  ! PRINT level for energy conserv. diag.
138      SAVE      ip_ebil_dyn
139      DATA      ip_ebil_dyn/0/
140c-jld
141
142      LOGICAL offline  ! Controle du stockage ds "fluxmass"
143      PARAMETER (offline=.false.)
144
145      character*80 dynhist_file, dynhistave_file
146      character*20 modname
147      character*80 abort_message
148
149C Calendrier
150      LOGICAL true_calendar
151      PARAMETER (true_calendar = .false.)
152C Run nudge
153      LOGICAL ok_nudge
154      PARAMETER (ok_nudge = .false.)
155
156c-----------------------------------------------------------------------
157c   Initialisations:
158c   ----------------
159
160      abort_message = 'last timestep reached'
161      modname = 'gcm'
162      descript = 'Run GCM LMDZ'
163      lafin    = .FALSE.
164      dynhist_file = 'dyn_hist.nc'
165      dynhistave_file = 'dyn_hist_ave.nc'
166
167      if (true_calendar) then
168        call ioconf_calendar('gregorian')
169      else
170        call ioconf_calendar('360d')
171      endif
172c-----------------------------------------------------------------------
173c
174c  ....  Choix  des shemas d'advection pour l'eau et les traceurs  ...
175c  ...................................................................
176c
177c     iadv = 1    shema  transport type "humidite specifique LMD" 
178c     iadv = 2    shema   amont
179c     iadv = 3    shema  Van-leer
180c     iadv = 4    schema  Van-leer + humidite specifique
181c                        Modif F.Codron
182c
183c     dans le tableau q(ij,l,iq) , iq = 1  pour l'eau vapeur
184c                                , iq = 2  pour l'eau liquide
185c         et eventuellement      , iq = 3, nqmx pour les autres traceurs
186c
187      DO iq = 1, nqmx
188       iadv( iq ) = 3
189      ENDDO
190c
191c     iadv(1): choix pour l'eau vap. et  iadv(2) : choix pour l'eau liq.
192      iadv( 1 ) = 4
193c
194       IF( iadv(1).EQ.1 ) PRINT *,' Choix du shema humidite specifique'
195     * ,' pour la vapeur d''eau'
196       IF( iadv(1).EQ.2 ) PRINT *,' Choix du shema  amont',' pour la'
197     * ,' vapeur d''eau '
198       IF( iadv(1).EQ.3 ) PRINT *,' Choix du shema  Van-Leer ',' pour'
199     * ,'la vapeur d''eau'
200       IF( iadv(1).EQ.4 ) PRINT *,' Choix du shema  Van-Leer + humidite'
201     * ,' specifique pour la vapeur d''eau'
202c
203       IF( iadv(1).LE.0.OR.iadv(1).GT.4 )   THEN
204        PRINT *,' Erreur dans le choix de iadv (1).Corriger et repasser
205     * ,  car  iadv(1) = ', iadv(1)
206         CALL ABORT
207       ENDIF
208
209      DO  iq = 2, nqmx
210       IF( iadv(iq).EQ.1 ) PRINT *,' Choix du shema humidite specifique'
211     * ,' pour le traceur no ', iq
212       IF( iadv(iq).EQ.2 ) PRINT *,' Choix du shema  amont',' pour le'
213     * ,' traceur no ', iq
214       IF( iadv(iq).EQ.3 ) PRINT *,' Choix du shema  Van-Leer ',' pour'
215     * ,'le traceur no ', iq
216
217       IF( iadv(iq).EQ.4 )  THEN
218         PRINT *,' Le shema  Van-Leer + humidite specifique ',
219     * ' est  uniquement pour la vapeur d eau .'
220         PRINT *,' Corriger iadv( ',iq, ')  et repasser ! '
221         CALL ABORT
222       ENDIF
223
224       IF( iadv(iq).LE.0.OR.iadv(iq).GT.4 )   THEN
225       PRINT *,' Erreur dans le  choix de  iadv . Corriger et repasser
226     * . '
227         CALL ABORT
228       ENDIF
229      ENDDO
230c
231      first = .TRUE.
232      numvanle = nqmx + 1
233      DO  iq = 1, nqmx
234        IF((iadv(iq).EQ.3.OR.iadv(iq).EQ.4).AND.first ) THEN
235          numvanle = iq
236          first    = .FALSE.
237        ENDIF
238      ENDDO
239c
240      DO  iq = 1, nqmx
241      IF( (iadv(iq).NE.3.AND.iadv(iq).NE.4).AND.iq.GT.numvanle )  THEN
242          PRINT *,' Il y a discontinuite dans le choix du shema de ',
243     *    'Van-leer pour les traceurs . Corriger et repasser . '
244           CALL ABORT
245      ENDIF
246        IF( iadv(iq).LT.1.OR.iadv(iq).GT.4 )    THEN
247          PRINT *,' Le choix de  iadv  est errone pour le traceur ',
248     *    iq
249         STOP
250        ENDIF
251      ENDDO
252c
253
254      CALL dynetat0("start.nc",nqmx,vcov,ucov,
255     .              teta,q,masse,ps,phis, time_0)
256
257
258c     OPEN( 99,file ='run.def',status='old',form='formatted')
259c      CALL defrun_new( 99, .TRUE. , clesphy0 )
260      CALL conf_gcm( 99, .TRUE. , clesphy0 )
261c     CLOSE(99)
262
263c  on recalcule eventuellement le pas de temps
264
265      IF(MOD(day_step,iperiod).NE.0)
266     * STOP'Il faut choisir un nb de pas par jour multiple de iperiod'
267
268      IF(MOD(day_step,iphysiq).NE.0)
269     * STOP'Il faut choisir un nb de pas par jour multiple de iphysiq'
270
271      zdtvr    = daysec/FLOAT(day_step)
272        IF(dtvr.NE.zdtvr) THEN
273         PRINT*,'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
274        ENDIF
275C
276C on remet le calendrier à zero
277c
278      if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then
279        write(*,*)' Attention les dates initiales lues dans le fichier'
280        write(*,*)' restart ne correspondent pas a celles lues dans '
281        write(*,*)' gcm.def'
282        if (raz_date .ne. 1) then
283          write(*,*)' On garde les dates du fichier restart'
284        else
285          annee_ref = anneeref
286          day_ref = dayref
287          itau_dyn = 0
288          itau_phy = 0
289          time_0 = 0.
290          write(*,*)' On reinitialise a la date lue dans gcm.def'
291        endif
292      ELSE
293        raz_date = 0
294      endif
295
296c  nombre d'etats dans les fichiers demarrage et histoire
297      nbetatdem = nday / iecri
298      nbetatmoy = nday / periodav + 1
299
300      dtvr = zdtvr
301      CALL iniconst
302      CALL inigeom
303
304      CALL inifilr
305c
306c   ......    P.Le Van    ( modif  le 29/04/97 )   ......... 
307c
308      CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   ,
309     *                tetagdiv, tetagrot , tetatemp              )
310c+jld
311C     initialisation constantes thermo utilisees dans diagedyn
312      IF (ip_ebil_dyn.ge.1 ) THEN
313        CALL suphec
314      ENDIF
315c-jld
316c
317
318      CALL pression ( ip1jmp1, ap, bp, ps, p       )
319      CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
320c
321
322c  numero de stockage pour les fichiers de redemarrage:
323
324c-----------------------------------------------------------------------
325c   temps de depart et de fin:
326c   --------------------------
327
328      itau = 0
329      iday = day_ini+itau/day_step
330      time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
331         IF(time.GT.1.) THEN
332          time = time-1.
333          iday = iday+1
334         ENDIF
335      itaufin   = nday*day_step
336      itaufinp1 = itaufin +1
337
338      day_end = day_ini + nday
339      PRINT 300, itau,itaufin,day_ini,day_end
340
341      CALL dynredem0("restart.nc", day_end, phis, nqmx)
342
343      ecripar = .TRUE.
344
345      time_step = zdtvr
346      t_ops = iecri * daysec
347      t_wrt = iecri * daysec
348C      CALL inithist(dynhist_file,day_ref,annee_ref,time_step,
349c     .              t_ops, t_wrt, nqmx, histid, histvid)
350
351      t_ops = iperiod * time_step
352      t_wrt = periodav * daysec
353      CALL initdynav(dynhistave_file,day_ref,annee_ref,time_step,
354     .              t_ops, t_wrt, nqmx, histaveid)
355
356      dtav = iperiod*dtvr/daysec
357
358
359c   Quelques initialisations pour les traceurs
360      call initial0(ijp1llm*nqmx,dq)
361      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
362      istphy=istdyn/iphysiq
363
364c-----------------------------------------------------------------------
365c   Debut de l'integration temporelle:
366c   ----------------------------------
367
368   1  CONTINUE
369
370
371
372      if (ok_nudge) then
373        call nudge(itau,ucov,vcov,teta,masse,ps)
374      endif
375c
376c     IF( MOD( itau, 10* day_step ).EQ.0 )  THEN
377        CALL  test_period ( ucov,vcov,teta,q,p,phis )
378c        PRINT *,' ----   Test_period apres continue   OK ! -----', itau
379c     ENDIF
380c
381      CALL SCOPY( ijmllm ,vcov , 1, vcovm1 , 1 )
382      CALL SCOPY( ijp1llm,ucov , 1, ucovm1 , 1 )
383      CALL SCOPY( ijp1llm,teta , 1, tetam1 , 1 )
384      CALL SCOPY( ijp1llm,masse, 1, massem1, 1 )
385      CALL SCOPY( ip1jmp1, ps  , 1,   psm1 , 1 )
386
387      forward = .TRUE.
388      leapf   = .FALSE.
389      dt      =  dtvr
390
391c   ...    P.Le Van .26/04/94  ....
392
393      CALL SCOPY   ( ijp1llm,   masse, 1, finvmaold,     1 )
394      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
395
396
397   2  CONTINUE
398
399c-----------------------------------------------------------------------
400
401c   date:
402c   -----
403
404
405c   gestion des appels de la physique et des dissipations:
406c   ------------------------------------------------------
407c
408c   ...    P.Le Van  ( 6/02/95 )  ....
409
410      apphys = .FALSE.
411      statcl = .FALSE.
412      conser = .FALSE.
413      apdiss = .FALSE.
414
415      IF( purmats ) THEN
416         IF( MOD(itau,iconser) .EQ.0.AND.  forward    ) conser = .TRUE.
417         IF( MOD(itau,idissip ).EQ.0.AND..NOT.forward ) apdiss = .TRUE.
418         IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward
419     $                              .AND.   physic    ) apphys = .TRUE.
420      ELSE
421         IF( MOD(itau   ,iconser) .EQ. 0              ) conser = .TRUE.
422         IF( MOD(itau+1,idissip)  .EQ. 0              ) apdiss = .TRUE.
423         IF( MOD(itau+1,iphysiq).EQ.0. AND. physic    ) apphys = .TRUE.
424      END IF
425
426c-----------------------------------------------------------------------
427c   calcul des tendances dynamiques:
428c   --------------------------------
429
430      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
431c
432c
433      CALL caldyn
434     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
435     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time+iday-day_ini )
436
437c-----------------------------------------------------------------------
438c   calcul des tendances advection des traceurs (dont l'humidite)
439c   -------------------------------------------------------------
440
441      IF( forward. OR . leapf )  THEN
442c
443        DO 15  iq = 1, nqmx
444c
445         IF( iadv(iq).EQ.1.OR.iadv(iq).EQ.2 )  THEN
446           CALL traceur( iq,iadv,q,teta,pk,w, pbaru, pbarv, dq )
447
448         ELSE IF( iq.EQ. nqmx )   THEN
449c
450            iapp_tracvl = 5
451c
452cccc     iapp_tracvl est la frequence en pas du groupement des flux
453cccc      de masse pour  Van-Leer dans la routine  tracvl  .
454c
455            CALL vanleer(numvanle,iapp_tracvl,nqmx,q,pbaru,pbarv,
456     *                      p, masse, dq,  iadv(1), teta, pk     )
457c
458c                   ...  Modif  F.Codron  ....
459c
460         ENDIF
461c
462 15     CONTINUE
463C
464         IF (offline) THEN
465Cmaf stokage du flux de masse pour traceurs OFF-LINE
466
467            CALL fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
468     .   time_step, itau)
469
470
471         ENDIF
472c
473      ENDIF
474
475
476c-----------------------------------------------------------------------
477c   integrations dynamique et traceurs:
478c   ----------------------------------
479
480
481       CALL integrd ( iadv, 2,vcovm1,ucovm1,tetam1,psm1,massem1 ,
482     $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,
483     $              finvmaold                                    )
484
485c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
486c
487c-----------------------------------------------------------------------
488c   calcul des tendances physiques:
489c   -------------------------------
490c    ########   P.Le Van ( Modif le  6/02/95 )   ###########
491c
492       IF( purmats )  THEN
493          IF( itau.EQ.itaufin.AND..NOT.forward ) lafin = .TRUE.
494       ELSE
495          IF( itau+1. EQ. itaufin )              lafin = .TRUE.
496       ENDIF
497c
498c
499       IF( apphys )  THEN
500c
501c     .......   Ajout   P.Le Van ( 17/04/96 )   ...........
502c
503
504         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
505         CALL exner_hyb(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
506
507           rdaym_ini  = itau * dtvr / daysec
508           rdayvrai   = rdaym_ini  + day_ini
509
510           IF ( ecritphy.LT.1. )  THEN
511             rday_ecri = rdaym_ini
512           ELSE
513             rday_ecri = NINT( rdayvrai )
514           ENDIF
515c
516
517c rajout debug
518c       lafin = .true.
519c+jld
520      IF (ip_ebil_dyn.ge.1 ) THEN
521          ztit='bil dyn'
522          CALL diagedyn(ztit,2,1,1,dtphys
523     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
524     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
525      ENDIF
526c-jld
527        CALL calfis( nqmx, lafin ,rdayvrai,rday_ecri,time  ,
528     $                 ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
529     $     du,dv,dteta,dq,w,clesphy0, dufi,dvfi,dhfi,dqfi,dpfi  )
530
531c      ajout des tendances physiques:
532c      ------------------------------
533          CALL addfi( nqmx, dtphys, leapf, forward   ,
534     $                  ucov, vcov, teta , q   ,ps ,
535     $                 dufi, dvfi, dhfi , dqfi ,dpfi  )
536c
537c+jld
538      IF (ip_ebil_dyn.ge.1 ) THEN
539          ztit='bil phys'
540          CALL diagedyn(ztit,2,1,1,dtphys
541     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
542     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
543      ENDIF
544c-jld
545       ENDIF
546
547        CALL pression ( ip1jmp1, ap, bp, ps, p                  )
548        CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
549
550c-----------------------------------------------------------------------
551c
552c
553c   dissipation horizontale et verticale  des petites echelles:
554c   ----------------------------------------------------------
555
556      IF(apdiss) THEN
557c+jld
558      IF (ip_ebil_dyn.ge.2 ) THEN
559          ztit='avant dissip'
560          CALL diagedyn(ztit,2,2,2,dtvr
561     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
562     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
563      ENDIF
564        CALL covcont  ( llm    , ucov    , vcov , ucont, vcont        )
565        CALL enercin ( vcov   , ucov  , vcont     , ucont  , ecin0  )
566c-jld
567
568         CALL dissip(vcov,ucov,teta,p,dvdis,dudis,dhdis)
569
570         CALL addit( ijp1llm,ucov ,dudis,ucov )
571         CALL addit( ijmllm ,vcov ,dvdis,vcov )
572c+jld
573        CALL covcont  ( llm    , ucov    , vcov , ucont, vcont        )
574        CALL enercin ( vcov   , ucov  , vcont     , ucont  , ecin  )
575C
576C       On rajoute la tendance due a la transform. Ec -> E therm. cree
577C       lors de la dissipation
578        DO l  =  1, llm
579          DO    ij     = 1, ip1jmp1
580            dhecdt(ij,l)= (ecin0(ij,l)-ecin(ij,l))/ pk(ij,l)
581            dhdis(ij,l) = dhdis(ij,l) + dhecdt(ij,l)
582          ENDDO
583        ENDDO
584c-jld
585         CALL addit( ijp1llm,teta ,dhdis,teta )
586c+jld
587c
588         IF (ip_ebil_dyn.ge.2 ) THEN
589             ztit='apres dissip'
590             CALL diagedyn(ztit,2,2,2,dtdiss
591     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
592     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
593         ENDIF
594c-jld
595
596c    .......        P. Le Van (  ajout  le 17/04/96  )   ...........
597c   ...      Calcul de la valeur moyenne, unique de h aux poles  .....
598c
599
600        DO l  =  1, llm
601          DO ij =  1,iim
602           tppn(ij)  = aire(  ij    ) * teta(  ij    ,l)
603           tpps(ij)  = aire(ij+ip1jm) * teta(ij+ip1jm,l)
604          ENDDO
605           tpn  = SSUM(iim,tppn,1)/apoln
606           tps  = SSUM(iim,tpps,1)/apols
607
608          DO ij = 1, iip1
609           teta(  ij    ,l) = tpn
610           teta(ij+ip1jm,l) = tps
611          ENDDO
612        ENDDO
613
614        DO ij =  1,iim
615          tppn(ij)  = aire(  ij    ) * ps (  ij    )
616          tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
617        ENDDO
618          tpn  = SSUM(iim,tppn,1)/apoln
619          tps  = SSUM(iim,tpps,1)/apols
620
621        DO ij = 1, iip1
622          ps(  ij    ) = tpn
623          ps(ij+ip1jm) = tps
624        ENDDO
625
626
627      END IF
628
629c ajout debug
630c              IF( lafin ) then 
631c                abort_message = 'Simulation finished'
632c                call abort_gcm(modname,abort_message,0)
633c              ENDIF
634       
635c   ********************************************************************
636c   ********************************************************************
637c   .... fin de l'integration dynamique  et physique pour le pas itau ..
638c   ********************************************************************
639c   ********************************************************************
640
641c   preparation du pas d'integration suivant  ......
642
643      IF ( .NOT.purmats ) THEN
644c       ........................................................
645c       ..............  schema matsuno + leapfrog  ..............
646c       ........................................................
647
648            IF(forward. OR. leapf) THEN
649              itau= itau + 1
650              iday= day_ini+itau/day_step
651              time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
652                IF(time.GT.1.) THEN
653                  time = time-1.
654                  iday = iday+1
655                ENDIF
656            ENDIF
657
658
659            IF( itau. EQ. itaufinp1 ) then 
660
661              abort_message = 'Simulation finished'
662              call abort_gcm(modname,abort_message,0)
663            ENDIF
664c-----------------------------------------------------------------------
665c   ecriture du fichier histoire moyenne:
666c   -------------------------------------
667
668            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
669               IF(itau.EQ.itaufin) THEN
670                  iav=1
671               ELSE
672                  iav=0
673               ENDIF
674               CALL writedynav(histaveid, nqmx, itau,vcov ,
675     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
676cccIM cf. FH
677               call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
678     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
679
680            ENDIF
681
682c-----------------------------------------------------------------------
683c   ecriture de la bande histoire:
684c   ------------------------------
685
686            IF( MOD(itau,iecri*day_step).EQ.0) THEN
687
688               nbetat = nbetatdem
689       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi        )
690c       CALL writehist( histid, histvid, nqmx, itau,vcov ,
691c     ,                          ucov,teta,phi,q,masse,ps,phis)
692
693
694            ENDIF
695
696            IF(itau.EQ.itaufin) THEN
697
698
699       PRINT *,' Appel test_period avant redem ', itau
700       CALL  test_period ( ucov,vcov,teta,q,p,phis )
701       CALL dynredem1("restart.nc",0.0,
702     .                     vcov,ucov,teta,q,nqmx,masse,ps)
703
704              CLOSE(99)
705            ENDIF
706
707c-----------------------------------------------------------------------
708c   gestion de l'integration temporelle:
709c   ------------------------------------
710
711            IF( MOD(itau,iperiod).EQ.0 )    THEN
712                    GO TO 1
713            ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
714
715                   IF( forward )  THEN
716c      fin du pas forward et debut du pas backward
717
718                      forward = .FALSE.
719                        leapf = .FALSE.
720                           GO TO 2
721
722                   ELSE
723c      fin du pas backward et debut du premier pas leapfrog
724
725                        leapf =  .TRUE.
726                        dt  =  2.*dtvr
727                        GO TO 2
728                   END IF
729            ELSE
730
731c      ......   pas leapfrog  .....
732
733                 leapf = .TRUE.
734                 dt  = 2.*dtvr
735                 GO TO 2
736            END IF
737
738      ELSE
739
740c       ........................................................
741c       ..............       schema  matsuno        ...............
742c       ........................................................
743            IF( forward )  THEN
744
745             itau =  itau + 1
746             iday = day_ini+itau/day_step
747             time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
748
749                  IF(time.GT.1.) THEN
750                   time = time-1.
751                   iday = iday+1
752                  ENDIF
753
754               forward =  .FALSE.
755               IF( itau. EQ. itaufinp1 ) then 
756                 abort_message = 'Simulation finished'
757                 call abort_gcm(modname,abort_message,0)
758               ENDIF
759               GO TO 2
760
761            ELSE
762
763            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
764               IF(itau.EQ.itaufin) THEN
765                  iav=1
766               ELSE
767                  iav=0
768               ENDIF
769               CALL writedynav(histaveid, nqmx, itau,vcov ,
770     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
771cccIM cf. FH
772               call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
773     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
774
775            ENDIF
776
777               IF(MOD(itau,iecri*day_step).EQ.0) THEN
778                  nbetat = nbetatdem
779       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi       )
780c       CALL writehist( histid, histvid, nqmx, itau,vcov ,
781c     ,                          ucov,teta,phi,q,masse,ps,phis)
782               ENDIF
783
784                 IF(itau.EQ.itaufin)
785     . CALL dynredem1("restart.nc",0.0,
786     .                     vcov,ucov,teta,q,nqmx,masse,ps)
787
788                 forward = .TRUE.
789                 GO TO  1
790
791            ENDIF
792
793      END IF
794
795 300  FORMAT('1'/,15x,'run du pas',i7,2x,'au pas',i7,2x, 
796     . 'c''est a dire du jour',i7,3x,'au jour',i7//)
797
798      STOP
799      END
Note: See TracBrowser for help on using the repository browser.