source: trunk/MESOSCALE/LMDZ.MARS/libf_gcm/dyn3d/defrun_new.F @ 832

Last change on this file since 832 was 57, checked in by aslmd, 14 years ago

mineur LMD_MM_MARS: ajout du GCM ancienne physique, systeme maintenant complet sur SVN (ne manque que la base de donnees d'etats initiaux)

File size: 15.8 KB
Line 
1      SUBROUTINE defrun_new( tapedef, etatinit )
2c
3      IMPLICIT NONE
4c-----------------------------------------------------------------------
5c     Auteurs :   L. Fairhead , P. Le Van  .
6c      Modif C. Hourdin F. Forget VERSION MARTIENNE
7c
8c
9c  -------------------------------------------------------------------
10c
11c                    MODIF JUIN 2000 (zoom)
12c       .........     Version  du 29/04/97       ..........
13c
14c   Nouveaux parametres nitergdiv,nitergrot,niterh,tetagdiv,tetagrot,
15c   tetatemp   ajoutes  pour la dissipation   .
16c
17c   Autre parametre ajoute en fin de liste : ** fxyhypb **
18c
19c   Si fxyhypb = .TRUE. , choix de la fonction a derivee tangente hyperb.
20c   Sinon , choix de fxynew  , a derivee sinusoidale  ..
21c
22c   ......  etatinit = . TRUE. si defrun_new  est appele dans NEWSTART
23c   ETAT0_LMD  ou  LIMIT_LMD  pour l'initialisation de start.dat (dic) et
24c   de limit.dat (dic)  ...........
25c   Sinon  etatinit = . FALSE .
26c
27c   Donc etatinit = .F.  si on veut comparer les valeurs de  alphax ,
28c   alphay,clon,clat, fxyhypb  lues sur  le fichier  start  avec
29c   celles passees  par run.def ,  au debut du gcm, apres l'appel a
30c   lectba . 
31c   Ces parametres definissant entre autres la grille et doivent etre
32c   pareils et coherents , sinon il y aura  divergence du gcm .
33c
34c
35c-----------------------------------------------------------------------
36c   Declarations :
37c   --------------
38
39#include "dimensions.h"
40#include "paramet.h"
41#include "control.h"
42#include "logic.h"
43#include "serre.h"
44#include "comdissnew.h"
45#include "sponge.h"
46c
47c   arguments:
48c   ---------
49      LOGICAL  etatinit ! should be .false. for a call from gcm.F
50                        ! and .true. for a call from newstart.F
51      INTEGER  tapedef  ! unit number to assign to 'run.def' file
52c
53c   local variables:
54c   ---------------
55
56      CHARACTER ch1*72,ch2*72,ch3*72,ch4*8 ! to store various strings
57      INTEGER tapeout ! unit numbers for (standard) outputs
58      parameter (tapeout=6)
59      integer tapeerr ! unit number for error message
60      parameter (tapeerr=0)
61
62c     REAL clonn,clatt,alphaxx,alphayy
63c     LOGICAL  fxyhypbb
64      INTEGER ierr
65      REAL clonn,clatt,grossismxx,grossismyy
66      REAL dzoomxx,dzoomyy,tauxx,tauyy,temp
67      LOGICAL  fxyhypbb, ysinuss
68
69
70c   initialisations:
71c   ----------------
72 
73!      tapeout=6
74
75c-----------------------------------------------------------------------
76c  Parametres de controle du run:
77c-----------------------------------------------------------------------
78
79
80!Initialisation des parametres "terrestres", qui ne concernent pas
81!le modele martien et ne sont donc plus lues dans "run.def"
82
83        anneeref=0
84        ! Note: anneref is a common in 'control.h'
85
86      OPEN(tapedef,file='run.def',status='old',form='formatted'
87     .     ,iostat=ierr)
88
89      IF(ierr.EQ.0) THEN ! if file run.def is found
90
91        WRITE(tapeout,*) "DEFRUN: reading file run.def"
92        READ (tapedef,9000) ch1,ch2,ch3
93        WRITE(tapeout,9000) ch1,ch2,ch3
94
95        READ (tapedef,9001) ch1,ch4
96        READ (tapedef,*)    nday
97        WRITE(tapeout,9002) ch1
98        WRITE(tapeout,9005) 'nday       ',nday
99
100        READ (tapedef,9001) ch1,ch4
101        READ (tapedef,*)    day_step
102        WRITE(tapeout,9002) ch1
103        WRITE(tapeout,9005) 'day_step   ',day_step
104
105        READ (tapedef,9001) ch1,ch4
106        READ (tapedef,*)    iperiod
107        WRITE(tapeout,9002) ch1
108        WRITE(tapeout,9005) 'iperiod    ',iperiod
109
110        READ (tapedef,9001) ch1,ch4
111        READ (tapedef,*)    iconser
112        WRITE(tapeout,9002) ch1
113        WRITE(tapeout,9005) 'iconser    ',iconser
114
115        READ (tapedef,9001) ch1,ch4
116        READ (tapedef,*)    temp
117        WRITE(tapeout,9002) ch1
118        WRITE(tapeout,9006) 'iecri not used'
119
120        READ (tapedef,9001) ch1,ch4
121        READ (tapedef,*)    periodav
122        WRITE(tapeout,9002) ch1
123        WRITE(tapeout,9003) 'periodav   ',periodav
124
125        READ (tapedef,9001) ch1,ch4
126        READ (tapedef,*)    idissip
127        WRITE(tapeout,9002) ch1
128        WRITE(tapeout,9005) 'idissip    ',idissip
129
130ccc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
131ccc
132        READ (tapedef,9001) ch1,ch4
133        READ (tapedef,*)    lstardis
134        WRITE(tapeout,9002) ch1
135        WRITE(tapeout,9004) 'lstardis   ',lstardis
136
137        READ (tapedef,9001) ch1,ch4
138        READ (tapedef,*)    hybrid
139        WRITE(tapeout,9002) ch1
140        WRITE(tapeout,9004) 'hybrid ',hybrid
141
142        READ (tapedef,9001) ch1,ch4
143        READ (tapedef,*)    nitergdiv
144        WRITE(tapeout,9002) ch1
145        WRITE(tapeout,9005) 'nitergdiv  ',nitergdiv
146
147        READ (tapedef,9001) ch1,ch4
148        READ (tapedef,*)    nitergrot
149        WRITE(tapeout,9002) ch1
150        WRITE(tapeout,9005) 'nitergrot  ',nitergrot
151
152        READ (tapedef,9001) ch1,ch4
153        READ (tapedef,*)    niterh
154        WRITE(tapeout,9002) ch1
155        WRITE(tapeout,9005) 'niterh     ',niterh
156
157        READ (tapedef,9001) ch1,ch4
158        READ (tapedef,*)    tetagdiv
159        WRITE(tapeout,9002) ch1
160        WRITE(tapeout,9003) 'tetagdiv   ',tetagdiv
161
162        READ (tapedef,9001) ch1,ch4
163        READ (tapedef,*)    tetagrot
164        WRITE(tapeout,9002) ch1
165        WRITE(tapeout,9003) 'tetagrot   ',tetagrot
166
167        READ (tapedef,9001) ch1,ch4
168        READ (tapedef,*)    tetatemp
169        WRITE(tapeout,9002) ch1
170        WRITE(tapeout,9003) 'tetatemp   ',tetatemp
171
172        READ (tapedef,9001) ch1,ch4
173        READ (tapedef,*)    coefdis
174        WRITE(tapeout,9002) ch1
175        WRITE(tapeout,9003) 'coefdis    ',coefdis
176c
177c    ...............................................................
178
179        READ (tapedef,9001) ch1,ch4
180        READ (tapedef,*)    purmats
181        WRITE(tapeout,9002) ch1
182        WRITE(tapeout,9004) 'purmats    ',purmats
183
184        READ (tapedef,9001) ch1,ch4
185        READ (tapedef,*)    physic
186        WRITE(tapeout,9002) ch1
187        WRITE(tapeout,9004) 'physic     ',physic
188
189        READ (tapedef,9001) ch1,ch4
190        READ (tapedef,*)    iphysiq
191        WRITE(tapeout,9002) ch1
192        WRITE(tapeout,9005) 'iphysiq    ',iphysiq
193
194        READ (tapedef,9001) ch1,ch4
195        READ (tapedef,*)    grireg
196        WRITE(tapeout,9002) ch1
197        WRITE(tapeout,9004) 'grireg     ',grireg
198
199ccc   .... P.Le Van, ajout le 03/01/96 pour l'ecriture phys ...
200c
201        READ (tapedef,9001) ch1,ch4
202        READ (tapedef,*)    ecritphy
203        WRITE(tapeout,9002) ch1
204        WRITE(tapeout,9003) 'ecritphy   ',ecritphy
205
206
207ccc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
208c     .........   (  modif  le 17/04/96 )   .........
209c
210        if (.not.etatinit ) then
211
212           READ (tapedef,9001) ch1,ch4
213           READ (tapedef,*)    clonn
214           WRITE(tapeout,9002) ch1
215           WRITE(tapeout,9003) 'clon       ',clonn
216           IF( ABS(clon - clonn).GE. 0.001 )  THEN
217             PRINT *,' La valeur de clon passee par run.def est '
218     *       ,'differente de celle lue sur le fichier start '
219             STOP
220           ENDIF
221c
222c
223           READ (tapedef,9001) ch1,ch4
224           READ (tapedef,*)    clatt
225           WRITE(tapeout,9002) ch1
226           WRITE(tapeout,9003) 'clat       ',clatt
227 
228           IF( ABS(clat - clatt).GE. 0.001 )  THEN
229             PRINT *,' La valeur de clat passee par run.def est '
230     *       ,'differente de celle lue sur le fichier start '
231             STOP
232           ENDIF
233
234           READ (tapedef,9001) ch1,ch4
235           READ (tapedef,*)    grossismxx
236           WRITE(tapeout,9002) ch1
237           WRITE(tapeout,9003) 'grossismx  ',grossismxx
238
239           if(grossismxx.eq.0) then 
240             write(*,*)
241             write(*,*)'ERREUR : dans run.def, grossismx =0'
242             write(*,*)'Attention a ne pas utiliser une version de'
243             write(*,*)'run.def avant le nouveau zoom LMDZ2.3 (06/2000)'
244             write(*,*)'(Il faut ajouter grossismx,dzoomx,etc... a la'
245             write(*,*)'place de alphax, alphay. cf. dyn3d). '
246             write(*,*)
247             stop
248           end if
249
250           IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
251             PRINT *,' La valeur de grossismx passee par run.def est '
252     *       ,'differente de celle lue sur le fichier  start =',
253     *        grossismx
254             if (grossismx.eq.0) then
255                  write(*,*) 'OK,Normal : c est un vieux start'
256     *             , 'd avant le nouveau zoom LMDZ2.3 (06/2000)'
257                 grossismx=grossismxx
258             else
259                   STOP
260             endif
261           ENDIF
262
263           READ (tapedef,9001) ch1,ch4
264           READ (tapedef,*)    grossismyy
265           WRITE(tapeout,9002) ch1
266           WRITE(tapeout,9003) 'grossismy  ',grossismyy
267
268           IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
269             PRINT *,' La valeur de grossismy passee par run.def est '
270     *       ,'differente de celle lue sur le fichier  start =',
271     *        grossismy
272             if (grossismy.eq.0) then
273                  write(*,*) 'OK,Normal : c est un vieux start'
274     *             , 'd avant le nouveau zoom LMDZ2.3 (06/2000)'
275                 grossismy=grossismyy
276             else
277                   STOP
278             endif
279           ENDIF
280
281
282           IF( grossismx.LT.1. )  THEN
283             PRINT *,' ***  ATTENTION !! grossismx < 1 .   *** '
284             STOP
285           ELSE
286             alphax = 1. - 1./ grossismx
287           ENDIF
288
289           IF( grossismy.LT.1. )  THEN
290             PRINT *,' ***  ATTENTION !! grossismy < 1 .   *** '
291             STOP
292           ELSE
293             alphay = 1. - 1./ grossismy
294           ENDIF
295
296           PRINT *,' '
297           PRINT *,' --> In defrun: alphax alphay  ',alphax,alphay
298           PRINT *,' '
299c
300           READ (tapedef,9001) ch1,ch4
301           READ (tapedef,*)    fxyhypbb
302           WRITE(tapeout,9002) ch1
303           WRITE(tapeout,9004) 'fxyhypbb   ',fxyhypbb
304 
305           IF( .NOT.fxyhypb )  THEN
306             IF( fxyhypbb )     THEN
307                PRINT *,' ********  PBS DANS  DEFRUN  ******** '
308                PRINT *,' *** fxyhypb lu sur le fichier start est F ',
309     *          'alors  qu il est  T  sur  run.def  ***'
310                STOP
311             ENDIF
312           ELSE
313             IF( .NOT.fxyhypbb )   THEN
314                PRINT *,' ********  PBS DANS  DEFRUN  ******** '
315                PRINT *,' ***  fxyhypb lu sur le fichier start est T ',
316     *         'alors  qu il est  F  sur  run.def  ****  '
317                STOP
318             ENDIF
319           ENDIF
320           READ (tapedef,9001) ch1,ch4
321           READ (tapedef,*)    dzoomxx
322           WRITE(tapeout,9002) ch1
323           WRITE(tapeout,9003) 'dzoomx  ',dzoomxx
324
325           IF( fxyhypb )  THEN
326              IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
327                PRINT *,' La valeur de dzoomx passee par run.def est '
328     *          ,'differente de celle lue sur le fichier  start '
329                STOP
330              ENDIF
331           ENDIF
332
333           READ (tapedef,9001) ch1,ch4
334           READ (tapedef,*)    dzoomyy
335           WRITE(tapeout,9002) ch1
336           WRITE(tapeout,9003) 'dzoomy  ',dzoomyy
337
338           IF( fxyhypb )  THEN
339              IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
340                PRINT *,' La valeur de dzoomy passee par run.def est '
341     *          ,'differente de celle lue sur le fichier  start '
342                STOP
343              ENDIF
344           ENDIF
345
346           READ (tapedef,9001) ch1,ch4
347           READ (tapedef,*)    tauxx
348           WRITE(tapeout,9001) ch1,'taux'
349           WRITE(tapeout,*)    tauxx
350
351           READ (tapedef,9001) ch1,ch4
352           READ (tapedef,*)    tauyy
353           WRITE(tapeout,9001) ch1,'tauy'
354           WRITE(tapeout,*)    tauyy
355
356           IF( fxyhypb )  THEN
357              IF( ABS(taux - tauxx).GE. 0.001 )  THEN
358                WRITE(6,*)' La valeur de taux passee par run.def est',
359     *             'differente de celle lue sur le fichier  start '
360                CALL ABORT
361              ENDIF
362
363              IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
364                WRITE(6,*)' La valeur de tauy passee par run.def est',
365     *          'differente de celle lue sur le fichier  start '
366                CALL ABORT
367              ENDIF
368           ENDIF
369 
370        ELSE    ! Below, case when etainit=.true.
371
372           READ (tapedef,9001) ch1,ch4
373           READ (tapedef,*)    clon
374           WRITE(tapeout,9002) ch1
375           WRITE(tapeout,9003) 'clon       ',clon
376c
377           READ (tapedef,9001) ch1,ch4
378           READ (tapedef,*)    clat
379           WRITE(tapeout,9002) ch1
380           WRITE(tapeout,9003) 'clat       ',clat
381
382           READ (tapedef,9001) ch1,ch4
383           READ (tapedef,*)    grossismx
384           WRITE(tapeout,9002) ch1
385           WRITE(tapeout,9003) 'grossismx  ',grossismx
386
387           READ (tapedef,9001) ch1,ch4
388           READ (tapedef,*)    grossismy
389           WRITE(tapeout,9002) ch1
390           WRITE(tapeout,9003) 'grossismy  ',grossismy
391
392           IF( grossismx.LT.1. )  THEN
393            PRINT *,' ***  ATTENTION !! grossismx < 1 .   *** '
394            STOP
395           ELSE
396             alphax = 1. - 1./ grossismx
397           ENDIF
398
399           IF( grossismy.LT.1. )  THEN
400             PRINT *,' ***  ATTENTION !! grossismy < 1 .   *** '
401             STOP
402           ELSE
403             alphay = 1. - 1./ grossismy
404           ENDIF
405
406           PRINT *,' Defrun  alphax alphay  ',alphax,alphay
407c
408           READ (tapedef,9001) ch1,ch4
409           READ (tapedef,*)    fxyhypb
410           WRITE(tapeout,9002) ch1
411           WRITE(tapeout,9004) 'fxyhypb  ',fxyhypb
412
413           READ (tapedef,9001) ch1,ch4
414           READ (tapedef,*)    dzoomx
415           WRITE(tapeout,9002) ch1
416           WRITE(tapeout,9003) 'dzoomx   ',dzoomx
417
418           READ (tapedef,9001) ch1,ch4
419           READ (tapedef,*)    dzoomy
420           WRITE(tapeout,9002) ch1
421           WRITE(tapeout,9003) 'dzoomy   ',dzoomy
422
423           READ (tapedef,9001) ch1,ch4
424           READ (tapedef,*)    taux
425           WRITE(tapeout,9001) ch1,'taux'
426           WRITE(tapeout,*)    taux
427
428           READ (tapedef,9001) ch1,ch4
429           READ (tapedef,*)    tauy
430           WRITE(tapeout,9001) ch1,'tauy'
431           WRITE(tapeout,*)    tauy
432
433        END IF ! of if (.not.etatinit )
434
435        READ (tapedef,9001) ch1,ch4
436        READ (tapedef,*)    ysinus
437        WRITE(tapeout,9001) ch1,'ysinus'
438        WRITE(tapeout,*)    ysinus
439
440        READ (tapedef,9001) ch1,ch4
441        READ (tapedef,*)    callsponge
442        WRITE(tapeout,9002) ch1
443        WRITE(tapeout,9004) 'callsponge ',callsponge
444
445        READ (tapedef,9001) ch1,ch4
446        READ (tapedef,*)    mode_sponge
447        WRITE(tapeout,9002) ch1
448        WRITE(tapeout,9005) 'mode_sponge',mode_sponge
449
450        READ (tapedef,9001) ch1,ch4
451        READ (tapedef,*)    hsponge
452        WRITE(tapeout,9002) ch1
453        WRITE(tapeout,9003) 'hsponge    ',hsponge
454
455        READ (tapedef,9001) ch1,ch4
456        READ (tapedef,*)    tetasponge
457        WRITE(tapeout,9002) ch1
458        WRITE(tapeout,9003) 'tetasponge ',tetasponge
459
460
461      WRITE(tapeout,*) '-----------------------------------------------'
462      WRITE(tapeout,*) ' '
463      WRITE(tapeout,*) ' '
464c
465
466c       Unlike on Earth (cf LMDZ2.2) , always a regular grid on Mars :
467        ysinus = .false. !Mars Mettre a jour
468
469
470      WRITE(tapeout,*) '-----------------------------------------------'
471      WRITE(tapeout,*) ' '
472      WRITE(tapeout,*) ' '
473cc
474      ELSE
475        write(tapeerr,*) ' WHERE IS run.def ? WE NEED IT !!!!!!!!!!!!!!'
476        stop
477      ENDIF ! of IF(ierr.eq.0)
478
479c     Test sur le zoom
480
481      if((grossismx.eq.1).and.(grossismy.eq.1)) then 
482c        Pas de zoom :
483         write(tapeout,*) 'No zoom ? -> fxyhypb set to False'
484     &   ,'           (It runs better that way)'
485         fxyhypb = .false.
486      else     
487c        Avec Zoom
488         if (.not.fxyhypb) stop 'With zoom, fxyhypb should be set to T
489     &in run.def for this version... -> STOP ! '     
490      end if
491
492      RETURN
493c
4949000  FORMAT(3(/,a72))
4959001  FORMAT(/,a72,/,a9)
4969002  FORMAT(/,a72)
4979003  FORMAT(t3,a11,t14,f9.3)
4989004  FORMAT(t3,a11,t14,l9)
4999005  FORMAT(t3,a11,t14,i9)
5009006  FORMAT(t3,a14)
501      END
Note: See TracBrowser for help on using the repository browser.