source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/config/ppsrc/dyn3d_common/defrun.f @ 224

Last change on this file since 224 was 224, checked in by ymipsl, 10 years ago
File size: 18.8 KB
Line 
1!
2! $Id: defrun.F 1403 2010-07-01 09:02:53Z fairhead $
3!
4c
5c
6      SUBROUTINE defrun( tapedef, etatinit, clesphy0 )
7c
8! ========================== ATTENTION =============================
9! COMMENTAIRE SL :
10! NE SERT PLUS APPAREMMENT
11! DONC PAS MIS A JOUR POUR L'UTILISATION AVEC LES PLANETES
12! ==================================================================
13
14      USE control_mod
15 
16      IMPLICIT NONE
17c-----------------------------------------------------------------------
18c     Auteurs :   L. Fairhead , P. Le Van  .
19c
20c     Arguments :
21c
22c     tapedef   :
23c     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para- 
24c     -metres  du zoom  avec  celles lues sur le fichier start .
25c      clesphy0 :  sortie  .
26c
27       LOGICAL etatinit
28       INTEGER tapedef
29
30       INTEGER        longcles
31       PARAMETER(     longcles = 20 )
32       REAL clesphy0( longcles )
33c
34c   Declarations :
35c   --------------
36!-----------------------------------------------------------------------
37!   INCLUDE 'dimensions.h'
38!
39!   dimensions.h contient les dimensions du modele
40!   ndm est tel que iim=2**ndm
41!-----------------------------------------------------------------------
42
43      INTEGER iim,jjm,llm,ndm
44
45      PARAMETER (iim= 128,jjm=96,llm=64,ndm=1)
46
47!-----------------------------------------------------------------------
48!
49! $Header$
50!
51!
52!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
53!                 veillez  n'utiliser que des ! pour les commentaires
54!                 et  bien positionner les & des lignes de continuation
55!                 (les placer en colonne 6 et en colonne 73)
56!
57!
58!-----------------------------------------------------------------------
59!   INCLUDE 'paramet.h'
60
61      INTEGER  iip1,iip2,iip3,jjp1,llmp1,llmp2,llmm1
62      INTEGER  kftd,ip1jm,ip1jmp1,ip1jmi1,ijp1llm
63      INTEGER  ijmllm,mvar
64      INTEGER jcfil,jcfllm
65
66      PARAMETER( iip1= iim+1,iip2=iim+2,iip3=iim+3                       &
67     &    ,jjp1=jjm+1-1/jjm)
68      PARAMETER( llmp1 = llm+1,  llmp2 = llm+2, llmm1 = llm-1 )
69      PARAMETER( kftd  = iim/2 -ndm )
70      PARAMETER( ip1jm  = iip1*jjm,  ip1jmp1= iip1*jjp1 )
71      PARAMETER( ip1jmi1= ip1jm - iip1 )
72      PARAMETER( ijp1llm= ip1jmp1 * llm, ijmllm= ip1jm * llm )
73      PARAMETER( mvar= ip1jmp1*( 2*llm+1) + ijmllm )
74      PARAMETER( jcfil=jjm/2+5, jcfllm=jcfil*llm )
75
76!-----------------------------------------------------------------------
77!
78! $Id: logic.h 1520 2011-05-23 11:37:09Z emillour $
79!
80!
81! NB: keep items of different kinds in seperate common blocs to avoid
82!     "misaligned commons" issues
83!-----------------------------------------------------------------------
84! INCLUDE 'logic.h'
85
86      COMMON/logicl/ purmats,forward,leapf,apphys,                      &
87     &  statcl,conser,apdiss,apdelq,saison,ecripar,fxyhypb,ysinus       &
88     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
89     &  ,ok_limit,ok_etat0,hybrid                                       &
90     &  ,moyzon_mu,moyzon_ch
91
92      COMMON/logici/ iflag_phys,iflag_trac
93     
94      LOGICAL purmats,forward,leapf,apphys,statcl,conser,               &
95     & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus                      &
96     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
97     &  ,ok_limit,ok_etat0
98      logical hybrid ! vertical coordinate is hybrid if true (sigma otherwise)
99                     ! (only used if disvert_type==2)
100      logical moyzon_mu,moyzon_ch ! used for zonal averages in Titan
101
102      integer iflag_phys,iflag_trac
103!$OMP THREADPRIVATE(/logicl/)
104!$OMP THREADPRIVATE(/logici/)
105!-----------------------------------------------------------------------
106!
107! $Header$
108!
109!c
110!c
111!c..include serre.h
112!c
113       REAL clon,clat,transx,transy,alphax,alphay,pxo,pyo,              &
114     &  grossismx, grossismy, dzoomx, dzoomy,taux,tauy
115       COMMON/serre/clon,clat,transx,transy,alphax,alphay,pxo,pyo ,     &
116     &  grossismx, grossismy, dzoomx, dzoomy,taux,tauy
117!
118! $Id: comdissnew.h 1319 2010-02-23 21:29:54Z fairhead $
119!
120!
121!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
122!                 veillez à n'utiliser que des ! pour les commentaires
123!                 et à bien positionner les & des lignes de continuation
124!                 (les placer en colonne 6 et en colonne 73)
125!
126!-----------------------------------------------------------------------
127! INCLUDE 'comdissnew.h'
128
129      COMMON/comdissnew/ lstardis,nitergdiv,nitergrot,niterh,tetagdiv,  &
130     &                   tetagrot,tetatemp,coefdis, vert_prof_dissip
131
132      LOGICAL lstardis
133      INTEGER nitergdiv, nitergrot, niterh
134
135! For the Earth model:
136      integer vert_prof_dissip ! vertical profile of horizontal dissipation
137!     Allowed values:
138!     0: rational fraction, function of pressure
139!     1: tanh of altitude
140
141      REAL     tetagdiv, tetagrot,  tetatemp, coefdis
142
143!
144! ... Les parametres de ce common comdissnew sont  lues par defrun_new
145!              sur le fichier  run.def    ....
146!
147!-----------------------------------------------------------------------
148!
149! $Header$
150!
151! NE SERT A RIEN !! A VIRER... PAS A JOUR !!!
152
153c..include clesph0.h
154c
155       COMMON/clesph0/cycle_diurne, soil_model,new_oliq, ok_orodr ,
156     ,                ok_orolf ,ok_limitvrai, nbapp_rad, iflag_con
157c
158       LOGICAL cycle_diurne,soil_model,ok_orodr,ok_orolf,new_oliq
159       LOGICAL ok_limitvrai
160       INTEGER nbapp_rad, iflag_con
161c
162c
163c   local:
164c   ------
165
166      CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
167      INTEGER   tapeout
168      REAL clonn,clatt,grossismxx,grossismyy
169      REAL dzoomxx,dzoomyy,tauxx,tauyy
170      LOGICAL  fxyhypbb, ysinuss
171      INTEGER i
172     
173c
174c  -------------------------------------------------------------------
175c
176c       .........     Version  du 29/04/97       ..........
177c
178c   Nouveaux parametres nitergdiv,nitergrot,niterh,tetagdiv,tetagrot,
179c      tetatemp   ajoutes  pour la dissipation   .
180c
181c   Autre parametre ajoute en fin de liste de tapedef : ** fxyhypb ** 
182c
183c  Si fxyhypb = .TRUE. , choix de la fonction a derivee tangente hyperb.
184c    Sinon , choix de fxynew  , a derivee sinusoidale  ..
185c
186c   ......  etatinit = . TRUE. si defrun  est appele dans ETAT0_LMD  ou
187c         LIMIT_LMD  pour l'initialisation de start.dat (dic) et
188c                de limit.dat ( dic)                        ...........
189c           Sinon  etatinit = . FALSE .
190c
191c   Donc etatinit = .F.  si on veut comparer les valeurs de  grossismx ,
192c    grossismy,clon,clat, fxyhypb  lues sur  le fichier  start  avec
193c   celles passees  par run.def ,  au debut du gcm, apres l'appel a 
194c    lectba . 
195c   Ces parmetres definissant entre autres la grille et doivent etre
196c   pareils et coherents , sinon il y aura  divergence du gcm .
197c
198c-----------------------------------------------------------------------
199c   initialisations:
200c   ----------------
201
202      tapeout = 6
203
204c-----------------------------------------------------------------------
205c  Parametres de controle du run:
206c-----------------------------------------------------------------------
207
208      OPEN( tapedef,file ='gcm.def',status='old',form='formatted')
209
210
211      READ (tapedef,9000) ch1,ch2,ch3
212      WRITE(tapeout,9000) ch1,ch2,ch3
213
214      READ (tapedef,9001) ch1,ch4
215      READ (tapedef,*)    dayref
216      WRITE(tapeout,9001) ch1,'dayref'
217      WRITE(tapeout,*)    dayref
218
219      READ (tapedef,9001) ch1,ch4
220      READ (tapedef,*)    anneeref
221      WRITE(tapeout,9001) ch1,'anneeref'
222      WRITE(tapeout,*)    anneeref
223
224      READ (tapedef,9001) ch1,ch4
225      READ (tapedef,*)    nday
226      WRITE(tapeout,9001) ch1,'nday'
227      WRITE(tapeout,*)    nday
228
229      READ (tapedef,9001) ch1,ch4
230      READ (tapedef,*)    day_step
231      WRITE(tapeout,9001) ch1,'day_step'
232      WRITE(tapeout,*)    day_step
233
234      READ (tapedef,9001) ch1,ch4
235      READ (tapedef,*)    iperiod
236      WRITE(tapeout,9001) ch1,'iperiod'
237      WRITE(tapeout,*)    iperiod
238
239      READ (tapedef,9001) ch1,ch4
240      READ (tapedef,*)    iapp_tracvl
241      WRITE(tapeout,9001) ch1,'iapp_tracvl'
242      WRITE(tapeout,*)    iapp_tracvl
243
244      READ (tapedef,9001) ch1,ch4
245      READ (tapedef,*)    iconser
246      WRITE(tapeout,9001) ch1,'iconser'
247      WRITE(tapeout,*)    iconser
248
249      READ (tapedef,9001) ch1,ch4
250      READ (tapedef,*)    iecri
251      WRITE(tapeout,9001) ch1,'iecri'
252      WRITE(tapeout,*)    iecri
253
254      READ (tapedef,9001) ch1,ch4
255      READ (tapedef,*)    periodav
256      WRITE(tapeout,9001) ch1,'periodav'
257      WRITE(tapeout,*)    periodav
258
259      READ (tapedef,9001) ch1,ch4
260      READ (tapedef,*)    dissip_period
261      WRITE(tapeout,9001) ch1,'dissip_period'
262      WRITE(tapeout,*)    dissip_period
263
264ccc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
265ccc
266      READ (tapedef,9001) ch1,ch4
267      READ (tapedef,*)    lstardis
268      WRITE(tapeout,9001) ch1,'lstardis'
269      WRITE(tapeout,*)    lstardis
270
271      READ (tapedef,9001) ch1,ch4
272      READ (tapedef,*)    nitergdiv
273      WRITE(tapeout,9001) ch1,'nitergdiv'
274      WRITE(tapeout,*)    nitergdiv
275
276      READ (tapedef,9001) ch1,ch4
277      READ (tapedef,*)    nitergrot
278      WRITE(tapeout,9001) ch1,'nitergrot'
279      WRITE(tapeout,*)    nitergrot
280
281      READ (tapedef,9001) ch1,ch4
282      READ (tapedef,*)    niterh
283      WRITE(tapeout,9001) ch1,'niterh'
284      WRITE(tapeout,*)    niterh
285
286      READ (tapedef,9001) ch1,ch4
287      READ (tapedef,*)    tetagdiv
288      WRITE(tapeout,9001) ch1,'tetagdiv'
289      WRITE(tapeout,*)    tetagdiv
290
291      READ (tapedef,9001) ch1,ch4
292      READ (tapedef,*)    tetagrot
293      WRITE(tapeout,9001) ch1,'tetagrot'
294      WRITE(tapeout,*)    tetagrot
295
296      READ (tapedef,9001) ch1,ch4
297      READ (tapedef,*)    tetatemp
298      WRITE(tapeout,9001) ch1,'tetatemp'
299      WRITE(tapeout,*)    tetatemp
300
301      READ (tapedef,9001) ch1,ch4
302      READ (tapedef,*)    coefdis
303      WRITE(tapeout,9001) ch1,'coefdis'
304      WRITE(tapeout,*)    coefdis
305c
306      READ (tapedef,9001) ch1,ch4
307      READ (tapedef,*)    purmats
308      WRITE(tapeout,9001) ch1,'purmats'
309      WRITE(tapeout,*)    purmats
310
311c    ...............................................................
312
313      READ (tapedef,9001) ch1,ch4
314      READ (tapedef,*)    iflag_phys
315      WRITE(tapeout,9001) ch1,'iflag_phys'
316      WRITE(tapeout,*)    iflag_phys
317
318      READ (tapedef,9001) ch1,ch4
319      READ (tapedef,*)    iphysiq
320      WRITE(tapeout,9001) ch1,'iphysiq'
321      WRITE(tapeout,*)    iphysiq
322
323
324      READ (tapedef,9001) ch1,ch4
325      READ (tapedef,*)    cycle_diurne
326      WRITE(tapeout,9001) ch1,'cycle_diurne'
327      WRITE(tapeout,*)    cycle_diurne
328
329      READ (tapedef,9001) ch1,ch4
330      READ (tapedef,*)    soil_model
331      WRITE(tapeout,9001) ch1,'soil_model'
332      WRITE(tapeout,*)    soil_model
333
334      READ (tapedef,9001) ch1,ch4
335      READ (tapedef,*)    new_oliq
336      WRITE(tapeout,9001) ch1,'new_oliq'
337      WRITE(tapeout,*)    new_oliq
338
339      READ (tapedef,9001) ch1,ch4
340      READ (tapedef,*)    ok_orodr
341      WRITE(tapeout,9001) ch1,'ok_orodr'
342      WRITE(tapeout,*)    ok_orodr
343
344      READ (tapedef,9001) ch1,ch4
345      READ (tapedef,*)    ok_orolf
346      WRITE(tapeout,9001) ch1,'ok_orolf'
347      WRITE(tapeout,*)    ok_orolf
348
349      READ (tapedef,9001) ch1,ch4
350      READ (tapedef,*)    ok_limitvrai
351      WRITE(tapeout,9001) ch1,'ok_limitvrai'
352      WRITE(tapeout,*)    ok_limitvrai
353
354      READ (tapedef,9001) ch1,ch4
355      READ (tapedef,*)    nbapp_rad
356      WRITE(tapeout,9001) ch1,'nbapp_rad'
357      WRITE(tapeout,*)    nbapp_rad
358
359      READ (tapedef,9001) ch1,ch4
360      READ (tapedef,*)    iflag_con
361      WRITE(tapeout,9001) ch1,'iflag_con'
362      WRITE(tapeout,*)    iflag_con
363
364      DO i = 1, longcles
365       clesphy0(i) = 0.
366      ENDDO
367                          clesphy0(1) = REAL( iflag_con )
368                          clesphy0(2) = REAL( nbapp_rad )
369
370       IF( cycle_diurne  ) clesphy0(3) =  1.
371       IF(   soil_model  ) clesphy0(4) =  1.
372       IF(     new_oliq  ) clesphy0(5) =  1.
373       IF(     ok_orodr  ) clesphy0(6) =  1.
374       IF(     ok_orolf  ) clesphy0(7) =  1.
375       IF(  ok_limitvrai ) clesphy0(8) =  1.
376
377
378ccc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
379c     .........   (  modif  le 17/04/96 )   .........
380c
381      IF( etatinit ) GO TO 100
382
383      READ (tapedef,9001) ch1,ch4
384      READ (tapedef,*)    clonn
385      WRITE(tapeout,9001) ch1,'clon'
386      WRITE(tapeout,*)    clonn
387      IF( ABS(clon - clonn).GE. 0.001 )  THEN
388       WRITE(tapeout,*) ' La valeur de clon passee par run.def est diffe
389     *rente de  celle lue sur le fichier  start '
390        STOP
391      ENDIF
392c
393      READ (tapedef,9001) ch1,ch4
394      READ (tapedef,*)    clatt
395      WRITE(tapeout,9001) ch1,'clat'
396      WRITE(tapeout,*)    clatt
397
398      IF( ABS(clat - clatt).GE. 0.001 )  THEN
399       WRITE(tapeout,*) ' La valeur de clat passee par run.def est diffe
400     *rente de  celle lue sur le fichier  start '
401        STOP
402      ENDIF
403
404      READ (tapedef,9001) ch1,ch4
405      READ (tapedef,*)    grossismxx
406      WRITE(tapeout,9001) ch1,'grossismx'
407      WRITE(tapeout,*)    grossismxx
408
409      IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
410       WRITE(tapeout,*) ' La valeur de grossismx passee par run.def est
411     , differente de celle lue sur le fichier  start '
412        STOP
413      ENDIF
414
415      READ (tapedef,9001) ch1,ch4
416      READ (tapedef,*)    grossismyy
417      WRITE(tapeout,9001) ch1,'grossismy'
418      WRITE(tapeout,*)    grossismyy
419
420      IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
421       WRITE(tapeout,*) ' La valeur de grossismy passee par run.def est
422     , differente de celle lue sur le fichier  start '
423        STOP
424      ENDIF
425     
426      IF( grossismx.LT.1. )  THEN
427        WRITE(tapeout,*) ' ***  ATTENTION !! grossismx < 1 .   *** '
428         STOP
429      ELSE
430         alphax = 1. - 1./ grossismx
431      ENDIF
432
433
434      IF( grossismy.LT.1. )  THEN
435        WRITE(tapeout,*) ' ***  ATTENTION !! grossismy < 1 .   *** '
436         STOP
437      ELSE
438         alphay = 1. - 1./ grossismy
439      ENDIF
440
441c
442c    alphax et alphay sont les anciennes formulat. des grossissements
443c
444c
445      READ (tapedef,9001) ch1,ch4
446      READ (tapedef,*)    fxyhypbb
447      WRITE(tapeout,9001) ch1,'fxyhypbb'
448      WRITE(tapeout,*)    fxyhypbb
449
450      IF( .NOT.fxyhypb )  THEN
451           IF( fxyhypbb )     THEN
452            WRITE(tapeout,*) ' ********  PBS DANS  DEFRUN  ******** '
453            WRITE(tapeout,*)' *** fxyhypb lu sur le fichier start est F'
454     *,      '                   alors  qu il est  T  sur  run.def  ***'
455              STOP
456           ENDIF
457      ELSE
458           IF( .NOT.fxyhypbb )   THEN
459            WRITE(tapeout,*) ' ********  PBS DANS  DEFRUN  ******** '
460            WRITE(tapeout,*)' *** fxyhypb lu sur le fichier start est t'
461     *,      '                   alors  qu il est  F  sur  run.def  ***'
462              STOP
463           ENDIF
464      ENDIF
465c
466      READ (tapedef,9001) ch1,ch4
467      READ (tapedef,*)    dzoomxx
468      WRITE(tapeout,9001) ch1,'dzoomx'
469      WRITE(tapeout,*)    dzoomxx
470
471      READ (tapedef,9001) ch1,ch4
472      READ (tapedef,*)    dzoomyy
473      WRITE(tapeout,9001) ch1,'dzoomy'
474      WRITE(tapeout,*)    dzoomyy
475
476      READ (tapedef,9001) ch1,ch4
477      READ (tapedef,*)    tauxx
478      WRITE(tapeout,9001) ch1,'taux'
479      WRITE(tapeout,*)    tauxx
480
481      READ (tapedef,9001) ch1,ch4
482      READ (tapedef,*)    tauyy
483      WRITE(tapeout,9001) ch1,'tauy'
484      WRITE(tapeout,*)    tauyy
485
486      IF( fxyhypb )  THEN
487
488       IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
489        WRITE(tapeout,*)' La valeur de dzoomx passee par run.def est dif
490     *ferente de celle lue sur le fichier  start '
491        CALL ABORT_gcm("defrun", "", 1)
492       ENDIF
493
494       IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
495        WRITE(tapeout,*)' La valeur de dzoomy passee par run.def est dif
496     *ferente de celle lue sur le fichier  start '
497        CALL ABORT_gcm("defrun", "", 1)
498       ENDIF
499
500       IF( ABS(taux - tauxx).GE. 0.001 )  THEN
501        WRITE(6,*)' La valeur de taux passee par run.def est differente
502     *  de celle lue sur le fichier  start '
503        CALL ABORT_gcm("defrun", "", 1)
504       ENDIF
505
506       IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
507        WRITE(6,*)' La valeur de tauy passee par run.def est differente
508     *  de celle lue sur le fichier  start '
509        CALL ABORT_gcm("defrun", "", 1)
510       ENDIF
511
512      ENDIF
513     
514cc
515      IF( .NOT.fxyhypb  )  THEN
516        READ (tapedef,9001) ch1,ch4
517        READ (tapedef,*)    ysinuss
518        WRITE(tapeout,9001) ch1,'ysinus'
519        WRITE(tapeout,*)    ysinuss
520
521
522        IF( .NOT.ysinus )  THEN
523           IF( ysinuss )     THEN
524              WRITE(6,*) ' ********  PBS DANS  DEFRUN  ******** '
525              WRITE(tapeout,*)'** ysinus lu sur le fichier start est F',
526     *       ' alors  qu il est  T  sur  run.def  ***'
527              STOP
528           ENDIF
529        ELSE
530           IF( .NOT.ysinuss )   THEN
531              WRITE(6,*) ' ********  PBS DANS  DEFRUN  ******** '
532              WRITE(tapeout,*)'** ysinus lu sur le fichier start est T',
533     *       ' alors  qu il est  F  sur  run.def  ***'
534              STOP
535           ENDIF
536        ENDIF
537      ENDIF
538c
539      WRITE(6,*) ' alphax alphay defrun ',alphax,alphay
540
541      CLOSE(tapedef)
542
543      RETURN
544c   ...............................................
545c
546100   CONTINUE
547c
548      READ (tapedef,9001) ch1,ch4
549      READ (tapedef,*)    clon
550      WRITE(tapeout,9001) ch1,'clon'
551      WRITE(tapeout,*)    clon
552c
553      READ (tapedef,9001) ch1,ch4
554      READ (tapedef,*)    clat
555      WRITE(tapeout,9001) ch1,'clat'
556      WRITE(tapeout,*)    clat
557
558      READ (tapedef,9001) ch1,ch4
559      READ (tapedef,*)    grossismx
560      WRITE(tapeout,9001) ch1,'grossismx'
561      WRITE(tapeout,*)    grossismx
562
563      READ (tapedef,9001) ch1,ch4
564      READ (tapedef,*)    grossismy
565      WRITE(tapeout,9001) ch1,'grossismy'
566      WRITE(tapeout,*)    grossismy
567
568      IF( grossismx.LT.1. )  THEN
569        WRITE(tapeout,*) '***  ATTENTION !! grossismx < 1 .   *** '
570         STOP
571      ELSE
572         alphax = 1. - 1./ grossismx
573      ENDIF
574
575      IF( grossismy.LT.1. )  THEN
576        WRITE(tapeout,*) ' ***  ATTENTION !! grossismy < 1 .   *** '
577         STOP
578      ELSE
579         alphay = 1. - 1./ grossismy
580      ENDIF
581
582c
583      READ (tapedef,9001) ch1,ch4
584      READ (tapedef,*)    fxyhypb
585      WRITE(tapeout,9001) ch1,'fxyhypb'
586      WRITE(tapeout,*)    fxyhypb
587
588      READ (tapedef,9001) ch1,ch4
589      READ (tapedef,*)    dzoomx
590      WRITE(tapeout,9001) ch1,'dzoomx'
591      WRITE(tapeout,*)    dzoomx
592
593      READ (tapedef,9001) ch1,ch4
594      READ (tapedef,*)    dzoomy
595      WRITE(tapeout,9001) ch1,'dzoomy'
596      WRITE(tapeout,*)    dzoomy
597
598      READ (tapedef,9001) ch1,ch4
599      READ (tapedef,*)    taux
600      WRITE(tapeout,9001) ch1,'taux'
601      WRITE(tapeout,*)    taux
602c
603      READ (tapedef,9001) ch1,ch4
604      READ (tapedef,*)    tauy
605      WRITE(tapeout,9001) ch1,'tauy'
606      WRITE(tapeout,*)    tauy
607
608      READ (tapedef,9001) ch1,ch4
609      READ (tapedef,*)    ysinus
610      WRITE(tapeout,9001) ch1,'ysinus'
611      WRITE(tapeout,*)    ysinus
612       
613      WRITE(tapeout,*) ' alphax alphay defrun ',alphax,alphay
614c
6159000  FORMAT(3(/,a72))
6169001  FORMAT(/,a72,/,a12)
617cc
618      CLOSE(tapedef)
619
620      RETURN
621      END
Note: See TracBrowser for help on using the repository browser.