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

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

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