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

Last change on this file since 134 was 113, checked in by lmdzadmin, 24 years ago

rajout debug

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 19.9 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
361c-----------------------------------------------------------------------
362c   calcul des tendances advection des traceurs (dont l'humidite)
363c   -------------------------------------------------------------
364
365      IF( forward. OR . leapf )  THEN
366c
367        DO 15  iq = 1, nqmx
368c
369         IF( iadv(iq).EQ.1.OR.iadv(iq).EQ.2 )  THEN
370           CALL traceur( iq,iadv,q,teta,pk,w, pbaru, pbarv, dq )
371
372         ELSE IF( iq.EQ. nqmx )   THEN
373c
374            iapp_tracvl = 5
375c
376cccc     iapp_tracvl est la frequence en pas du groupement des flux
377cccc      de masse pour  Van-Leer dans la routine  tracvl  .
378c
379            CALL vanleer(numvanle,iapp_tracvl,nqmx,q,pbaru,pbarv,
380     *                             p,  masse, dq                  )
381c
382         ENDIF
383c
384 15     CONTINUE
385C
386         IF (offline) THEN
387Cmaf stokage du flux de masse pour traceurs OFF-LINE
388
389            CALL fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
390     .   time_step, itau,fluxid, fluxvid,fluxdid )
391
392         ENDIF
393c
394      ENDIF
395
396
397c-----------------------------------------------------------------------
398c   integrations dynamique et traceurs:
399c   ----------------------------------
400
401
402       CALL integrd ( iadv, 2,vcovm1,ucovm1,tetam1,psm1,massem1 ,
403     $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,
404     $              finvmaold                                    )
405
406c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
407c
408c-----------------------------------------------------------------------
409c   calcul des tendances physiques:
410c   -------------------------------
411c    ########   P.Le Van ( Modif le  6/02/95 )   ###########
412c
413       IF( purmats )  THEN
414          IF( itau.EQ.itaufin.AND..NOT.forward ) lafin = .TRUE.
415       ELSE
416          IF( itau+1. EQ. itaufin )              lafin = .TRUE.
417       ENDIF
418c
419c
420       IF( apphys )  THEN
421c
422c     .......   Ajout   P.Le Van ( 17/04/96 )   ...........
423c
424
425         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
426         CALL exner_hyb(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
427
428           rdaym_ini  = itau * dtvr / daysec
429           rdayvrai   = rdaym_ini  + day_ini
430
431           IF ( ecritphy.LT.1. )  THEN
432             rday_ecri = rdaym_ini
433           ELSE
434             rday_ecri = NINT( rdayvrai )
435           ENDIF
436c
437
438c rajout debug
439c       lafin = .true.
440
441        CALL calfis( nqmx, lafin ,rdayvrai,rday_ecri,time  ,
442     $                 ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
443     $     du,dv,dteta,dq,w,clesphy0, dufi,dvfi,dhfi,dqfi,dpfi  )
444
445c      ajout des tendances physiques:
446c      ------------------------------
447          CALL addfi( nqmx, dtphys, leapf, forward   ,
448     $                  ucov, vcov, teta , q   ,ps ,
449     $                 dufi, dvfi, dhfi , dqfi ,dpfi  )
450c
451       ENDIF
452
453        CALL pression ( ip1jmp1, ap, bp, ps, p                  )
454        CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
455
456c-----------------------------------------------------------------------
457c
458c
459c   dissipation horizontale et verticale  des petites echelles:
460c   ----------------------------------------------------------
461
462      IF(apdiss) THEN
463
464         CALL dissip(vcov,ucov,teta,p,dvdis,dudis,dhdis)
465
466         CALL addit( ijp1llm,ucov ,dudis,ucov )
467         CALL addit( ijmllm ,vcov ,dvdis,vcov )
468         CALL addit( ijp1llm,teta ,dhdis,teta )
469
470
471c    .......        P. Le Van (  ajout  le 17/04/96  )   ...........
472c   ...      Calcul de la valeur moyenne, unique de h aux poles  .....
473c
474
475        DO l  =  1, llm
476          DO ij =  1,iim
477           tppn(ij)  = aire(  ij    ) * teta(  ij    ,l)
478           tpps(ij)  = aire(ij+ip1jm) * teta(ij+ip1jm,l)
479          ENDDO
480           tpn  = SSUM(iim,tppn,1)/apoln
481           tps  = SSUM(iim,tpps,1)/apols
482
483          DO ij = 1, iip1
484           teta(  ij    ,l) = tpn
485           teta(ij+ip1jm,l) = tps
486          ENDDO
487        ENDDO
488
489        DO ij =  1,iim
490          tppn(ij)  = aire(  ij    ) * ps (  ij    )
491          tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
492        ENDDO
493          tpn  = SSUM(iim,tppn,1)/apoln
494          tps  = SSUM(iim,tpps,1)/apols
495
496        DO ij = 1, iip1
497          ps(  ij    ) = tpn
498          ps(ij+ip1jm) = tps
499        ENDDO
500
501
502      END IF
503
504c ajout debug
505c              IF( lafin ) then 
506c                abort_message = 'Simulation finished'
507c                call abort_gcm(modname,abort_message,0)
508c              ENDIF
509       
510c   ********************************************************************
511c   ********************************************************************
512c   .... fin de l'integration dynamique  et physique pour le pas itau ..
513c   ********************************************************************
514c   ********************************************************************
515
516c   preparation du pas d'integration suivant  ......
517
518      IF ( .NOT.purmats ) THEN
519c       ........................................................
520c       ..............  schema matsuno + leapfrog  ..............
521c       ........................................................
522
523            IF(forward. OR. leapf) THEN
524              itau= itau + 1
525              iday= day_ini+itau/day_step
526              time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
527                IF(time.GT.1.) THEN
528                  time = time-1.
529                  iday = iday+1
530                ENDIF
531            ENDIF
532
533
534            IF( itau. EQ. itaufinp1 ) then 
535              abort_message = 'Simulation finished'
536              call abort_gcm(modname,abort_message,0)
537            ENDIF
538c-----------------------------------------------------------------------
539c   ecriture du fichier histoire moyenne:
540c   -------------------------------------
541
542            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
543               IF(itau.EQ.itaufin) THEN
544                  iav=1
545               ELSE
546                  iav=0
547               ENDIF
548               CALL writedynav(histaveid, nqmx, itau,vcov ,
549     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
550            ENDIF
551
552c-----------------------------------------------------------------------
553c   ecriture de la bande histoire:
554c   ------------------------------
555
556            IF( MOD(itau,iecri*day_step).EQ.0) THEN
557
558               nbetat = nbetatdem
559       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi        )
560       CALL writehist( histid, histvid, nqmx, itau,vcov ,
561     ,                          ucov,teta,phi,q,masse,ps,phis)
562
563
564            ENDIF
565
566            IF(itau.EQ.itaufin) THEN
567
568
569       PRINT *,' Appel test_period avant redem ', itau
570       CALL  test_period ( ucov,vcov,teta,q,p,phis )
571       CALL dynredem1("restart.nc",0.0,
572     .                     vcov,ucov,teta,q,nqmx,masse,ps)
573
574              CLOSE(99)
575            ENDIF
576
577c-----------------------------------------------------------------------
578c   gestion de l'integration temporelle:
579c   ------------------------------------
580
581            IF( MOD(itau,iperiod).EQ.0 )    THEN
582                    GO TO 1
583            ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
584
585                   IF( forward )  THEN
586c      fin du pas forward et debut du pas backward
587
588                      forward = .FALSE.
589                        leapf = .FALSE.
590                           GO TO 2
591
592                   ELSE
593c      fin du pas backward et debut du premier pas leapfrog
594
595                        leapf =  .TRUE.
596                        dt  =  2.*dtvr
597                        GO TO 2
598                   END IF
599            ELSE
600
601c      ......   pas leapfrog  .....
602
603                 leapf = .TRUE.
604                 dt  = 2.*dtvr
605                 GO TO 2
606            END IF
607
608      ELSE
609
610c       ........................................................
611c       ..............       schema  matsuno        ...............
612c       ........................................................
613            IF( forward )  THEN
614
615             itau =  itau + 1
616             iday = day_ini+itau/day_step
617             time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
618
619                  IF(time.GT.1.) THEN
620                   time = time-1.
621                   iday = iday+1
622                  ENDIF
623
624               forward =  .FALSE.
625               IF( itau. EQ. itaufinp1 ) then 
626                 abort_message = 'Simulation finished'
627                 call abort_gcm(modname,abort_message,0)
628               ENDIF
629               GO TO 2
630
631            ELSE
632
633            IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
634               IF(itau.EQ.itaufin) THEN
635                  iav=1
636               ELSE
637                  iav=0
638               ENDIF
639               CALL writedynav(histaveid, nqmx, itau,vcov ,
640     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
641
642            ENDIF
643
644               IF(MOD(itau,iecri*day_step).EQ.0) THEN
645                  nbetat = nbetatdem
646       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi       )
647       CALL writehist( histid, histvid, nqmx, itau,vcov ,
648     ,                          ucov,teta,phi,q,masse,ps,phis)
649               ENDIF
650
651                 IF(itau.EQ.itaufin)
652     . CALL dynredem1("restart.nc",0.0,
653     .                     vcov,ucov,teta,q,nqmx,masse,ps)
654
655                 forward = .TRUE.
656                 GO TO  1
657
658            ENDIF
659
660      END IF
661
662 300  FORMAT('1'/,15x,'run du pas',i7,2x,'au pas',i7,2x, 
663     . 'c''est a dire du jour',i7,3x,'au jour',i7//)
664
665      STOP
666      END
Note: See TracBrowser for help on using the repository browser.