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

Last change on this file since 179 was 177, checked in by lmdzadmin, 24 years ago

Lots of stuff, plus particulierement:

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