source: LMDZ.3.3/trunk/libf/dyn3d/gcm.F @ 181

Last change on this file since 181 was 78, checked in by lmdz, 24 years ago

Modification de F.Codron pour le schema d'advection de l'eau

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 20.7 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)
128
129      LOGICAL offline  ! Controle du stockage ds "fluxmass"
130      PARAMETER (offline=.true.)
131
132      character*80 dynhist_file, dynhistave_file
133      character*20 modname
134      character*80 abort_message
135
136C Calendrier
137      LOGICAL true_calendar
138      PARAMETER (true_calendar = .false.)
139
140c-----------------------------------------------------------------------
141c   Initialisations:
142c   ----------------
143
144      modname = 'gcm'
145      descript = 'Run GCM LMDZ'
146      lafin    = .FALSE.
147      dynhist_file = 'dyn_hist.nc'
148      dynhistave_file = 'dyn_hist_ave.nc'
149
150      if (true_calendar) then
151        call ioconf_calendar('gregorian')
152      else
153        call ioconf_calendar('360d')
154      endif
155c-----------------------------------------------------------------------
156c
157c  ....  Choix  des shemas d'advection pour l'eau et les traceurs  ...
158c  ...................................................................
159c
160c     iadv = 1    shema  transport type "humidite specifique LMD" 
161c     iadv = 2    shema   amont
162c     iadv = 3    shema  Van-leer
163c     iadv = 4    schema  Van-leer + humidite specifique
164c                        Modif F.Codron
165c
166c     dans le tableau q(ij,l,iq) , iq = 1  pour l'eau vapeur
167c                                , iq = 2  pour l'eau liquide
168c         et eventuellement      , iq = 3, nqmx pour les autres traceurs
169c
170c     iadv(1): choix pour l'eau vap. et  iadv(2) : choix pour l'eau liq.
171c
172      DO iq = 1, nqmx
173       iadv( iq ) = 3
174      ENDDO
175c
176       IF( iadv(1).EQ.1 ) PRINT *,' Choix du shema humidite specifique'
177     * ,' pour la vapeur d''eau'
178       IF( iadv(1).EQ.2 ) PRINT *,' Choix du shema  amont',' pour la'
179     * ,' vapeur d''eau '
180       IF( iadv(1).EQ.3 ) PRINT *,' Choix du shema  Van-Leer ',' pour'
181     * ,'la vapeur d''eau'
182       IF( iadv(1).EQ.4 ) PRINT *,' Choix du shema  Van-Leer + humidite'
183     * ,' specifique pour la vapeur d''eau'
184c
185       IF( iadv(1).LE.0.OR.iadv(1).GT.4 )   THEN
186        PRINT *,' Erreur dans le choix de iadv (1).Corriger et repasser
187     * ,  car  iadv(1) = ', iadv(1)
188         CALL ABORT
189       ENDIF
190
191      DO  iq = 2, nqmx
192       IF( iadv(iq).EQ.1 ) PRINT *,' Choix du shema humidite specifique'
193     * ,' pour le traceur no ', iq
194       IF( iadv(iq).EQ.2 ) PRINT *,' Choix du shema  amont',' pour le'
195     * ,' traceur no ', iq
196       IF( iadv(iq).EQ.3 ) PRINT *,' Choix du shema  Van-Leer ',' pour'
197     * ,'le traceur no ', iq
198
199       IF( iadv(iq).EQ.4 )  THEN
200         PRINT *,' Le shema  Van-Leer + humidite specifique ',
201     * ' est  uniquement pour la vapeur d eau .'
202         PRINT *,' Corriger iadv( ',iq, ')  et repasser ! '
203         CALL ABORT
204       ENDIF
205
206       IF( iadv(iq).LE.0.OR.iadv(iq).GT.4 )   THEN
207       PRINT *,' Erreur dans le  choix de  iadv . Corriger et repasser
208     * . '
209         CALL ABORT
210       ENDIF
211      ENDDO
212c
213      first = .TRUE.
214      numvanle = nqmx + 1
215      DO  iq = 1, nqmx
216        IF((iadv(iq).EQ.3.OR.iadv(iq).EQ.4).AND.first ) THEN
217          numvanle = iq
218          first    = .FALSE.
219        ENDIF
220      ENDDO
221c
222      DO  iq = 1, nqmx
223      IF( (iadv(iq).NE.3.AND.iadv(iq).NE.4).AND.iq.GT.numvanle )  THEN
224          PRINT *,' Il y a discontinuite dans le choix du shema de ',
225     *    'Van-leer pour les traceurs . Corriger et repasser . '
226           CALL ABORT
227      ENDIF
228        IF( iadv(iq).LT.1.OR.iadv(iq).GT.4 )    THEN
229          PRINT *,' Le choix de  iadv  est errone pour le traceur ',
230     *    iq
231         STOP
232        ENDIF
233      ENDDO
234c
235
236      CALL dynetat0("start.nc",nqmx,vcov,ucov,
237     .              teta,q,masse,ps,phis, time_0)
238
239
240c     OPEN( 99,file ='run.def',status='old',form='formatted')
241      CALL defrun_new( 99, .TRUE. , clesphy0 )
242c     CLOSE(99)
243
244c  on recalcule eventuellement le pas de temps
245
246      IF(MOD(day_step,iperiod).NE.0)
247     * STOP'Il faut choisir un nb de pas par jour multiple de iperiod'
248
249      IF(MOD(day_step,iphysiq).NE.0)
250     * STOP'Il faut choisir un nb de pas par jour multiple de iphysiq'
251
252      zdtvr    = daysec/FLOAT(day_step)
253        IF(dtvr.NE.zdtvr) THEN
254         PRINT*,'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
255        ENDIF
256
257c  nombre d'etats dans les fichiers demarrage et histoire
258      nbetatdem = nday / iecri
259      nbetatmoy = nday / periodav + 1
260
261      dtvr = zdtvr
262      CALL iniconst
263      CALL inigeom
264
265      CALL inifilr
266c
267c   ......    P.Le Van    ( modif  le 29/04/97 )   ......... 
268c
269      CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   ,
270     *                tetagdiv, tetagrot , tetatemp              )
271c
272
273      CALL pression ( ip1jmp1, ap, bp, ps, p       )
274      CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
275c
276
277c  numero de stockage pour les fichiers de redemarrage:
278
279c-----------------------------------------------------------------------
280c   temps de depart et de fin:
281c   --------------------------
282
283      itau = 0
284      iday = day_ini+itau/day_step
285      time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
286         IF(time.GT.1.) THEN
287          time = time-1.
288          iday = iday+1
289         ENDIF
290      itaufin   = nday*day_step
291      itaufinp1 = itaufin +1
292
293      day_end = day_ini + nday
294      PRINT 300, itau,itaufin,day_ini,day_end
295
296      CALL dynredem0("restart.nc",day_end,anne_ini,phis,nqmx)
297
298      ecripar = .TRUE.
299
300      time_step = zdtvr
301      t_ops = iecri * daysec
302      t_wrt = iecri * daysec
303      CALL inithist(dynhist_file,day_ini,anne_ini,time_step,
304     .              t_ops, t_wrt, nqmx, histid, histvid)
305
306      t_ops = iperiod * time_step
307      t_wrt = periodav * daysec
308      CALL initdynav(dynhistave_file,day_ini,anne_ini,time_step,
309     .              t_ops, t_wrt, nqmx, histaveid)
310
311      dtav = iperiod*dtvr/daysec
312
313
314c   Quelques initialisations pour les traceurs
315      call initial0(ijp1llm*nqmx,dq)
316      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
317      istphy=istdyn/iphysiq
318
319c-----------------------------------------------------------------------
320c   Debut de l'integration temporelle:
321c   ----------------------------------
322
323   1  CONTINUE
324c     call nudge(itau,ucov,vcov,teta,masse,ps)
325c
326c     IF( MOD( itau, 10* day_step ).EQ.0 )  THEN
327        CALL  test_period ( ucov,vcov,teta,q,p,phis )
328        PRINT *,' ----   Test_period apres continue   OK ! -----', itau
329c     ENDIF
330c
331      CALL SCOPY( ijmllm ,vcov , 1, vcovm1 , 1 )
332      CALL SCOPY( ijp1llm,ucov , 1, ucovm1 , 1 )
333      CALL SCOPY( ijp1llm,teta , 1, tetam1 , 1 )
334      CALL SCOPY( ijp1llm,masse, 1, massem1, 1 )
335      CALL SCOPY( ip1jmp1, ps  , 1,   psm1 , 1 )
336
337      forward = .TRUE.
338      leapf   = .FALSE.
339      dt      =  dtvr
340
341c   ...    P.Le Van .26/04/94  ....
342
343      CALL SCOPY   ( ijp1llm,   masse, 1, finvmaold,     1 )
344      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
345
346
347   2  CONTINUE
348
349c-----------------------------------------------------------------------
350
351c   date:
352c   -----
353
354
355c   gestion des appels de la physique et des dissipations:
356c   ------------------------------------------------------
357c
358c   ...    P.Le Van  ( 6/02/95 )  ....
359
360      apphys = .FALSE.
361      statcl = .FALSE.
362      conser = .FALSE.
363      apdiss = .FALSE.
364
365      IF( purmats ) THEN
366         IF( MOD(itau,iconser) .EQ.0.AND.  forward    ) conser = .TRUE.
367         IF( MOD(itau,idissip ).EQ.0.AND..NOT.forward ) apdiss = .TRUE.
368         IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward
369     $                              .AND.   physic    ) apphys = .TRUE.
370      ELSE
371         IF( MOD(itau   ,iconser) .EQ. 0              ) conser = .TRUE.
372         IF( MOD(itau+1,idissip)  .EQ. 0              ) apdiss = .TRUE.
373         IF( MOD(itau+1,iphysiq).EQ.0. AND. physic    ) apphys = .TRUE.
374      END IF
375
376c-----------------------------------------------------------------------
377c   calcul des tendances dynamiques:
378c   --------------------------------
379
380      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
381c
382c
383      CALL caldyn
384     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
385     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time+iday-day_ini )
386
387c-----------------------------------------------------------------------
388c   calcul des tendances advection des traceurs (dont l'humidite)
389c   -------------------------------------------------------------
390
391      IF( forward. OR . leapf )  THEN
392c
393        DO 15  iq = 1, nqmx
394c
395         IF( iadv(iq).EQ.1.OR.iadv(iq).EQ.2 )  THEN
396           CALL traceur( iq,iadv,q,teta,pk,w, pbaru, pbarv, dq )
397
398         ELSE IF( iq.EQ. nqmx )   THEN
399c
400            iapp_tracvl = 5
401c
402cccc     iapp_tracvl est la frequence en pas du groupement des flux
403cccc      de masse pour  Van-Leer dans la routine  tracvl  .
404c
405            CALL vanleer(numvanle,iapp_tracvl,nqmx,q,pbaru,pbarv,
406     *                      p, masse, dq,  iadv(1), teta, pk     )
407c
408c                   ...  Modif  F.Codron  ....
409c
410         ENDIF
411c
412 15     CONTINUE
413C
414         IF (offline) THEN
415Cmaf stokage du flux de masse pour traceurs OFF-LINE
416
417            CALL fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
418     .   time_step, itau,fluxid, fluxvid,fluxdid )
419
420         ENDIF
421c
422      ENDIF
423
424
425c-----------------------------------------------------------------------
426c   integrations dynamique et traceurs:
427c   ----------------------------------
428
429
430       CALL integrd ( iadv, 2,vcovm1,ucovm1,tetam1,psm1,massem1 ,
431     $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,
432     $              finvmaold                                    )
433
434c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
435c
436c-----------------------------------------------------------------------
437c   calcul des tendances physiques:
438c   -------------------------------
439c    ########   P.Le Van ( Modif le  6/02/95 )   ###########
440c
441       IF( purmats )  THEN
442          IF( itau.EQ.itaufin.AND..NOT.forward ) lafin = .TRUE.
443       ELSE
444          IF( itau+1. EQ. itaufin )              lafin = .TRUE.
445       ENDIF
446c
447c
448       IF( apphys )  THEN
449c
450c     .......   Ajout   P.Le Van ( 17/04/96 )   ...........
451c
452
453         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
454         CALL exner_hyb(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
455
456           rdaym_ini  = itau * dtvr / daysec
457           rdayvrai   = rdaym_ini  + day_ini
458
459           IF ( ecritphy.LT.1. )  THEN
460             rday_ecri = rdaym_ini
461           ELSE
462             rday_ecri = NINT( rdayvrai )
463           ENDIF
464c
465        CALL calfis( nqmx, lafin ,rdayvrai,rday_ecri,time  ,
466     $                 ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
467     $     du,dv,dteta,dq,w,clesphy0, dufi,dvfi,dhfi,dqfi,dpfi  )
468
469c      ajout des tendances physiques:
470c      ------------------------------
471          CALL addfi( nqmx, dtphys, leapf, forward   ,
472     $                  ucov, vcov, teta , q   ,ps ,
473     $                 dufi, dvfi, dhfi , dqfi ,dpfi  )
474c
475       ENDIF
476
477        CALL pression ( ip1jmp1, ap, bp, ps, p                  )
478        CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
479
480c-----------------------------------------------------------------------
481c
482c
483c   dissipation horizontale et verticale  des petites echelles:
484c   ----------------------------------------------------------
485
486      IF(apdiss) THEN
487
488         CALL dissip(vcov,ucov,teta,p,dvdis,dudis,dhdis)
489
490         CALL addit( ijp1llm,ucov ,dudis,ucov )
491         CALL addit( ijmllm ,vcov ,dvdis,vcov )
492         CALL addit( ijp1llm,teta ,dhdis,teta )
493
494
495c    .......        P. Le Van (  ajout  le 17/04/96  )   ...........
496c   ...      Calcul de la valeur moyenne, unique de h aux poles  .....
497c
498
499        DO l  =  1, llm
500          DO ij =  1,iim
501           tppn(ij)  = aire(  ij    ) * teta(  ij    ,l)
502           tpps(ij)  = aire(ij+ip1jm) * teta(ij+ip1jm,l)
503          ENDDO
504           tpn  = SSUM(iim,tppn,1)/apoln
505           tps  = SSUM(iim,tpps,1)/apols
506
507          DO ij = 1, iip1
508           teta(  ij    ,l) = tpn
509           teta(ij+ip1jm,l) = tps
510          ENDDO
511        ENDDO
512
513        DO ij =  1,iim
514          tppn(ij)  = aire(  ij    ) * ps (  ij    )
515          tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
516        ENDDO
517          tpn  = SSUM(iim,tppn,1)/apoln
518          tps  = SSUM(iim,tpps,1)/apols
519
520        DO ij = 1, iip1
521          ps(  ij    ) = tpn
522          ps(ij+ip1jm) = tps
523        ENDDO
524
525
526      END IF
527       
528c   ********************************************************************
529c   ********************************************************************
530c   .... fin de l'integration dynamique  et physique pour le pas itau ..
531c   ********************************************************************
532c   ********************************************************************
533
534c   preparation du pas d'integration suivant  ......
535
536      IF ( .NOT.purmats ) THEN
537c       ........................................................
538c       ..............  schema matsuno + leapfrog  ..............
539c       ........................................................
540
541            IF(forward. OR. leapf) THEN
542              itau= itau + 1
543              iday= day_ini+itau/day_step
544              time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
545                IF(time.GT.1.) THEN
546                  time = time-1.
547                  iday = iday+1
548                ENDIF
549            ENDIF
550
551
552            IF( itau. EQ. itaufinp1 ) then 
553              abort_message = 'Simulation finished'
554              call abort_gcm(modname,abort_message,0)
555            ENDIF
556c-----------------------------------------------------------------------
557c   ecriture du fichier histoire moyenne:
558c   -------------------------------------
559
560            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
561               IF(itau.EQ.itaufin) THEN
562                  iav=1
563               ELSE
564                  iav=0
565               ENDIF
566               CALL writedynav(histaveid, nqmx, itau,vcov ,
567     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
568            ENDIF
569
570c-----------------------------------------------------------------------
571c   ecriture de la bande histoire:
572c   ------------------------------
573
574            IF( MOD(itau,iecri*day_step).EQ.0) THEN
575
576               nbetat = nbetatdem
577       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi        )
578       CALL writehist( histid, histvid, nqmx, itau,vcov ,
579     ,                          ucov,teta,phi,q,masse,ps,phis)
580
581
582            ENDIF
583
584            IF(itau.EQ.itaufin) THEN
585
586
587       PRINT *,' Appel test_period avant redem ', itau
588       CALL  test_period ( ucov,vcov,teta,q,p,phis )
589       CALL dynredem1("restart.nc",0.0,
590     .                     vcov,ucov,teta,q,nqmx,masse,ps)
591
592              CLOSE(99)
593            ENDIF
594
595c-----------------------------------------------------------------------
596c   gestion de l'integration temporelle:
597c   ------------------------------------
598
599            IF( MOD(itau,iperiod).EQ.0 )    THEN
600                    GO TO 1
601            ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
602
603                   IF( forward )  THEN
604c      fin du pas forward et debut du pas backward
605
606                      forward = .FALSE.
607                        leapf = .FALSE.
608                           GO TO 2
609
610                   ELSE
611c      fin du pas backward et debut du premier pas leapfrog
612
613                        leapf =  .TRUE.
614                        dt  =  2.*dtvr
615                        GO TO 2
616                   END IF
617            ELSE
618
619c      ......   pas leapfrog  .....
620
621                 leapf = .TRUE.
622                 dt  = 2.*dtvr
623                 GO TO 2
624            END IF
625
626      ELSE
627
628c       ........................................................
629c       ..............       schema  matsuno        ...............
630c       ........................................................
631            IF( forward )  THEN
632
633             itau =  itau + 1
634             iday = day_ini+itau/day_step
635             time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
636
637                  IF(time.GT.1.) THEN
638                   time = time-1.
639                   iday = iday+1
640                  ENDIF
641
642               forward =  .FALSE.
643               IF( itau. EQ. itaufinp1 ) then 
644                 abort_message = 'Simulation finished'
645                 call abort_gcm(modname,abort_message,0)
646               ENDIF
647               GO TO 2
648
649            ELSE
650
651            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
652               IF(itau.EQ.itaufin) THEN
653                  iav=1
654               ELSE
655                  iav=0
656               ENDIF
657               CALL writedynav(histaveid, nqmx, itau,vcov ,
658     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
659
660            ENDIF
661
662               IF(MOD(itau,iecri*day_step).EQ.0) THEN
663                  nbetat = nbetatdem
664       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi       )
665       CALL writehist( histid, histvid, nqmx, itau,vcov ,
666     ,                          ucov,teta,phi,q,masse,ps,phis)
667               ENDIF
668
669                 IF(itau.EQ.itaufin)
670     . CALL dynredem1("restart.nc",0.0,
671     .                     vcov,ucov,teta,q,nqmx,masse,ps)
672
673                 forward = .TRUE.
674                 GO TO  1
675
676            ENDIF
677
678      END IF
679
680 300  FORMAT('1'/,15x,'run du pas',i7,2x,'au pas',i7,2x, 
681     . 'c''est a dire du jour',i7,3x,'au jour',i7//)
682
683      STOP
684      END
Note: See TracBrowser for help on using the repository browser.