source: LMDZ.3.3/tags/IPSL-CM4_v2x1/libf/dyn3d/gcm.F @ 469

Last change on this file since 469 was 469, checked in by (none), 21 years ago

This commit was manufactured by cvs2svn to create tag
'IPSL-CM4_v2x1'.

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 24.2 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          write(*,*)' On reinitialise a la date lue dans gcm.def'
290        endif
291      endif
292
293c  nombre d'etats dans les fichiers demarrage et histoire
294      nbetatdem = nday / iecri
295      nbetatmoy = nday / periodav + 1
296
297      dtvr = zdtvr
298      CALL iniconst
299      CALL inigeom
300
301      CALL inifilr
302c
303c   ......    P.Le Van    ( modif  le 29/04/97 )   ......... 
304c
305      CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   ,
306     *                tetagdiv, tetagrot , tetatemp              )
307c+jld
308C     initialisation constantes thermo utilisees dans diagedyn
309      IF (ip_ebil_dyn.ge.1 ) THEN
310        CALL suphec
311      ENDIF
312c-jld
313c
314
315      CALL pression ( ip1jmp1, ap, bp, ps, p       )
316      CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
317c
318
319c  numero de stockage pour les fichiers de redemarrage:
320
321c-----------------------------------------------------------------------
322c   temps de depart et de fin:
323c   --------------------------
324
325      itau = 0
326      iday = day_ini+itau/day_step
327      time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
328         IF(time.GT.1.) THEN
329          time = time-1.
330          iday = iday+1
331         ENDIF
332      itaufin   = nday*day_step
333      itaufinp1 = itaufin +1
334
335      day_end = day_ini + nday
336      PRINT 300, itau,itaufin,day_ini,day_end
337
338      CALL dynredem0("restart.nc", day_end, phis, nqmx)
339
340      ecripar = .TRUE.
341
342      time_step = zdtvr
343      t_ops = iecri * daysec
344      t_wrt = iecri * daysec
345C      CALL inithist(dynhist_file,day_ref,annee_ref,time_step,
346c     .              t_ops, t_wrt, nqmx, histid, histvid)
347
348      t_ops = iperiod * time_step
349      t_wrt = periodav * daysec
350      CALL initdynav(dynhistave_file,day_ref,annee_ref,time_step,
351     .              t_ops, t_wrt, nqmx, histaveid)
352
353      dtav = iperiod*dtvr/daysec
354
355
356c   Quelques initialisations pour les traceurs
357      call initial0(ijp1llm*nqmx,dq)
358      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
359      istphy=istdyn/iphysiq
360
361c-----------------------------------------------------------------------
362c   Debut de l'integration temporelle:
363c   ----------------------------------
364
365   1  CONTINUE
366
367
368
369      if (ok_nudge) then
370        call nudge(itau,ucov,vcov,teta,masse,ps)
371      endif
372c
373c     IF( MOD( itau, 10* day_step ).EQ.0 )  THEN
374        CALL  test_period ( ucov,vcov,teta,q,p,phis )
375c        PRINT *,' ----   Test_period apres continue   OK ! -----', itau
376c     ENDIF
377c
378      CALL SCOPY( ijmllm ,vcov , 1, vcovm1 , 1 )
379      CALL SCOPY( ijp1llm,ucov , 1, ucovm1 , 1 )
380      CALL SCOPY( ijp1llm,teta , 1, tetam1 , 1 )
381      CALL SCOPY( ijp1llm,masse, 1, massem1, 1 )
382      CALL SCOPY( ip1jmp1, ps  , 1,   psm1 , 1 )
383
384      forward = .TRUE.
385      leapf   = .FALSE.
386      dt      =  dtvr
387
388c   ...    P.Le Van .26/04/94  ....
389
390      CALL SCOPY   ( ijp1llm,   masse, 1, finvmaold,     1 )
391      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
392
393
394   2  CONTINUE
395
396c-----------------------------------------------------------------------
397
398c   date:
399c   -----
400
401
402c   gestion des appels de la physique et des dissipations:
403c   ------------------------------------------------------
404c
405c   ...    P.Le Van  ( 6/02/95 )  ....
406
407      apphys = .FALSE.
408      statcl = .FALSE.
409      conser = .FALSE.
410      apdiss = .FALSE.
411
412      IF( purmats ) THEN
413         IF( MOD(itau,iconser) .EQ.0.AND.  forward    ) conser = .TRUE.
414         IF( MOD(itau,idissip ).EQ.0.AND..NOT.forward ) apdiss = .TRUE.
415         IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward
416     $                              .AND.   physic    ) apphys = .TRUE.
417      ELSE
418         IF( MOD(itau   ,iconser) .EQ. 0              ) conser = .TRUE.
419         IF( MOD(itau+1,idissip)  .EQ. 0              ) apdiss = .TRUE.
420         IF( MOD(itau+1,iphysiq).EQ.0. AND. physic    ) apphys = .TRUE.
421      END IF
422
423c-----------------------------------------------------------------------
424c   calcul des tendances dynamiques:
425c   --------------------------------
426
427      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
428c
429c
430      CALL caldyn
431     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
432     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time+iday-day_ini )
433
434c-----------------------------------------------------------------------
435c   calcul des tendances advection des traceurs (dont l'humidite)
436c   -------------------------------------------------------------
437
438      IF( forward. OR . leapf )  THEN
439c
440        DO 15  iq = 1, nqmx
441c
442         IF( iadv(iq).EQ.1.OR.iadv(iq).EQ.2 )  THEN
443           CALL traceur( iq,iadv,q,teta,pk,w, pbaru, pbarv, dq )
444
445         ELSE IF( iq.EQ. nqmx )   THEN
446c
447            iapp_tracvl = 5
448c
449cccc     iapp_tracvl est la frequence en pas du groupement des flux
450cccc      de masse pour  Van-Leer dans la routine  tracvl  .
451c
452            CALL vanleer(numvanle,iapp_tracvl,nqmx,q,pbaru,pbarv,
453     *                      p, masse, dq,  iadv(1), teta, pk     )
454c
455c                   ...  Modif  F.Codron  ....
456c
457         ENDIF
458c
459 15     CONTINUE
460C
461         IF (offline) THEN
462Cmaf stokage du flux de masse pour traceurs OFF-LINE
463
464            CALL fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
465     .   time_step, itau)
466
467
468         ENDIF
469c
470      ENDIF
471
472
473c-----------------------------------------------------------------------
474c   integrations dynamique et traceurs:
475c   ----------------------------------
476
477
478       CALL integrd ( iadv, 2,vcovm1,ucovm1,tetam1,psm1,massem1 ,
479     $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,
480     $              finvmaold                                    )
481
482c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
483c
484c-----------------------------------------------------------------------
485c   calcul des tendances physiques:
486c   -------------------------------
487c    ########   P.Le Van ( Modif le  6/02/95 )   ###########
488c
489       IF( purmats )  THEN
490          IF( itau.EQ.itaufin.AND..NOT.forward ) lafin = .TRUE.
491       ELSE
492          IF( itau+1. EQ. itaufin )              lafin = .TRUE.
493       ENDIF
494c
495c
496       IF( apphys )  THEN
497c
498c     .......   Ajout   P.Le Van ( 17/04/96 )   ...........
499c
500
501         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
502         CALL exner_hyb(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
503
504           rdaym_ini  = itau * dtvr / daysec
505           rdayvrai   = rdaym_ini  + day_ini
506
507           IF ( ecritphy.LT.1. )  THEN
508             rday_ecri = rdaym_ini
509           ELSE
510             rday_ecri = NINT( rdayvrai )
511           ENDIF
512c
513
514c rajout debug
515c       lafin = .true.
516c+jld
517      IF (ip_ebil_dyn.ge.1 ) THEN
518          ztit='bil dyn'
519          CALL diagedyn(ztit,2,1,1,dtphys
520     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
521     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
522      ENDIF
523c-jld
524        CALL calfis( nqmx, lafin ,rdayvrai,rday_ecri,time  ,
525     $                 ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
526     $     du,dv,dteta,dq,w,clesphy0, dufi,dvfi,dhfi,dqfi,dpfi  )
527
528c      ajout des tendances physiques:
529c      ------------------------------
530          CALL addfi( nqmx, dtphys, leapf, forward   ,
531     $                  ucov, vcov, teta , q   ,ps ,
532     $                 dufi, dvfi, dhfi , dqfi ,dpfi  )
533c
534c+jld
535      IF (ip_ebil_dyn.ge.1 ) THEN
536          ztit='bil phys'
537          CALL diagedyn(ztit,2,1,1,dtphys
538     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
539     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
540      ENDIF
541c-jld
542       ENDIF
543
544        CALL pression ( ip1jmp1, ap, bp, ps, p                  )
545        CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
546
547c-----------------------------------------------------------------------
548c
549c
550c   dissipation horizontale et verticale  des petites echelles:
551c   ----------------------------------------------------------
552
553      IF(apdiss) THEN
554c+jld
555      IF (ip_ebil_dyn.ge.2 ) THEN
556          ztit='avant dissip'
557          CALL diagedyn(ztit,2,2,2,dtvr
558     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
559     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
560      ENDIF
561        CALL covcont  ( llm    , ucov    , vcov , ucont, vcont        )
562        CALL enercin ( vcov   , ucov  , vcont     , ucont  , ecin0  )
563c-jld
564
565         CALL dissip(vcov,ucov,teta,p,dvdis,dudis,dhdis)
566
567         CALL addit( ijp1llm,ucov ,dudis,ucov )
568         CALL addit( ijmllm ,vcov ,dvdis,vcov )
569c+jld
570        CALL covcont  ( llm    , ucov    , vcov , ucont, vcont        )
571        CALL enercin ( vcov   , ucov  , vcont     , ucont  , ecin  )
572C
573C       On rajoute la tendance due a la transform. Ec -> E therm. cree
574C       lors de la dissipation
575        DO l  =  1, llm
576          DO    ij     = 1, ip1jmp1
577            dhecdt(ij,l)= (ecin0(ij,l)-ecin(ij,l))/ pk(ij,l)
578            dhdis(ij,l) = dhdis(ij,l) + dhecdt(ij,l)
579          ENDDO
580        ENDDO
581c-jld
582         CALL addit( ijp1llm,teta ,dhdis,teta )
583c+jld
584c
585         IF (ip_ebil_dyn.ge.2 ) THEN
586             ztit='apres dissip'
587             CALL diagedyn(ztit,2,2,2,dtdiss
588     e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2),aire
589     s  , d_h_vcol , d_qt, d_qw, d_ql, d_ec)
590         ENDIF
591c-jld
592
593c    .......        P. Le Van (  ajout  le 17/04/96  )   ...........
594c   ...      Calcul de la valeur moyenne, unique de h aux poles  .....
595c
596
597        DO l  =  1, llm
598          DO ij =  1,iim
599           tppn(ij)  = aire(  ij    ) * teta(  ij    ,l)
600           tpps(ij)  = aire(ij+ip1jm) * teta(ij+ip1jm,l)
601          ENDDO
602           tpn  = SSUM(iim,tppn,1)/apoln
603           tps  = SSUM(iim,tpps,1)/apols
604
605          DO ij = 1, iip1
606           teta(  ij    ,l) = tpn
607           teta(ij+ip1jm,l) = tps
608          ENDDO
609        ENDDO
610
611        DO ij =  1,iim
612          tppn(ij)  = aire(  ij    ) * ps (  ij    )
613          tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
614        ENDDO
615          tpn  = SSUM(iim,tppn,1)/apoln
616          tps  = SSUM(iim,tpps,1)/apols
617
618        DO ij = 1, iip1
619          ps(  ij    ) = tpn
620          ps(ij+ip1jm) = tps
621        ENDDO
622
623
624      END IF
625
626c ajout debug
627c              IF( lafin ) then 
628c                abort_message = 'Simulation finished'
629c                call abort_gcm(modname,abort_message,0)
630c              ENDIF
631       
632c   ********************************************************************
633c   ********************************************************************
634c   .... fin de l'integration dynamique  et physique pour le pas itau ..
635c   ********************************************************************
636c   ********************************************************************
637
638c   preparation du pas d'integration suivant  ......
639
640      IF ( .NOT.purmats ) THEN
641c       ........................................................
642c       ..............  schema matsuno + leapfrog  ..............
643c       ........................................................
644
645            IF(forward. OR. leapf) THEN
646              itau= itau + 1
647              iday= day_ini+itau/day_step
648              time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
649                IF(time.GT.1.) THEN
650                  time = time-1.
651                  iday = iday+1
652                ENDIF
653            ENDIF
654
655
656            IF( itau. EQ. itaufinp1 ) then 
657
658              abort_message = 'Simulation finished'
659              call abort_gcm(modname,abort_message,0)
660            ENDIF
661c-----------------------------------------------------------------------
662c   ecriture du fichier histoire moyenne:
663c   -------------------------------------
664
665            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
666               IF(itau.EQ.itaufin) THEN
667                  iav=1
668               ELSE
669                  iav=0
670               ENDIF
671               CALL writedynav(histaveid, nqmx, itau,vcov ,
672     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
673cccIM cf. FH
674               call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
675     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
676
677            ENDIF
678
679c-----------------------------------------------------------------------
680c   ecriture de la bande histoire:
681c   ------------------------------
682
683            IF( MOD(itau,iecri*day_step).EQ.0) THEN
684
685               nbetat = nbetatdem
686       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi        )
687c       CALL writehist( histid, histvid, nqmx, itau,vcov ,
688c     ,                          ucov,teta,phi,q,masse,ps,phis)
689
690
691            ENDIF
692
693            IF(itau.EQ.itaufin) THEN
694
695
696       PRINT *,' Appel test_period avant redem ', itau
697       CALL  test_period ( ucov,vcov,teta,q,p,phis )
698       CALL dynredem1("restart.nc",0.0,
699     .                     vcov,ucov,teta,q,nqmx,masse,ps)
700
701              CLOSE(99)
702            ENDIF
703
704c-----------------------------------------------------------------------
705c   gestion de l'integration temporelle:
706c   ------------------------------------
707
708            IF( MOD(itau,iperiod).EQ.0 )    THEN
709                    GO TO 1
710            ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
711
712                   IF( forward )  THEN
713c      fin du pas forward et debut du pas backward
714
715                      forward = .FALSE.
716                        leapf = .FALSE.
717                           GO TO 2
718
719                   ELSE
720c      fin du pas backward et debut du premier pas leapfrog
721
722                        leapf =  .TRUE.
723                        dt  =  2.*dtvr
724                        GO TO 2
725                   END IF
726            ELSE
727
728c      ......   pas leapfrog  .....
729
730                 leapf = .TRUE.
731                 dt  = 2.*dtvr
732                 GO TO 2
733            END IF
734
735      ELSE
736
737c       ........................................................
738c       ..............       schema  matsuno        ...............
739c       ........................................................
740            IF( forward )  THEN
741
742             itau =  itau + 1
743             iday = day_ini+itau/day_step
744             time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
745
746                  IF(time.GT.1.) THEN
747                   time = time-1.
748                   iday = iday+1
749                  ENDIF
750
751               forward =  .FALSE.
752               IF( itau. EQ. itaufinp1 ) then 
753                 abort_message = 'Simulation finished'
754                 call abort_gcm(modname,abort_message,0)
755               ENDIF
756               GO TO 2
757
758            ELSE
759
760            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
761               IF(itau.EQ.itaufin) THEN
762                  iav=1
763               ELSE
764                  iav=0
765               ENDIF
766               CALL writedynav(histaveid, nqmx, itau,vcov ,
767     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
768cccIM cf. FH
769               call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
770     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
771
772            ENDIF
773
774               IF(MOD(itau,iecri*day_step).EQ.0) THEN
775                  nbetat = nbetatdem
776       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi       )
777c       CALL writehist( histid, histvid, nqmx, itau,vcov ,
778c     ,                          ucov,teta,phi,q,masse,ps,phis)
779               ENDIF
780
781                 IF(itau.EQ.itaufin)
782     . CALL dynredem1("restart.nc",0.0,
783     .                     vcov,ucov,teta,q,nqmx,masse,ps)
784
785                 forward = .TRUE.
786                 GO TO  1
787
788            ENDIF
789
790      END IF
791
792 300  FORMAT('1'/,15x,'run du pas',i7,2x,'au pas',i7,2x, 
793     . 'c''est a dire du jour',i7,3x,'au jour',i7//)
794
795      STOP
796      END
Note: See TracBrowser for help on using the repository browser.