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

Last change on this file since 228 was 228, checked in by lmdzadmin, 23 years ago

detail dans l'initialisation
LF

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