source: trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/defrun_new.F

Last change on this file was 2354, checked in by emillour, 4 years ago

Generic GCM:
Major cleanup: remove obsolete compilation scripts (makegcm*) and old dynamical
core, as it is obsolete with respect to the one provide in LMDZ.COMMON.
EM

File size: 17.8 KB
Line 
1      SUBROUTINE defrun_new( tapedef, etatinit )
2#ifndef CPP_PARA
3c
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! to use  'getin'
39      USE ioipsl_getincom
40      use sponge_mod,only: callsponge,nsponge,mode_sponge,tetasponge
41      use control_mod,only: nday, day_step, iperiod, anneeref,
42     &                      iconser, dissip_period, iphysiq
43      USE logic_mod, ONLY: hybrid,purmats,fxyhypb,ysinus,iflag_phys
44      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,
45     .                  alphax,alphay,taux,tauy
46      IMPLICIT NONE
47
48#include "dimensions.h"
49#include "paramet.h"
50!#include "control.h"
51#include "comdissnew.h"
52#include "iniprint.h"
53c
54c   arguments:
55c   ---------
56      LOGICAL  etatinit ! should be .false. for a call from gcm.F
57                        ! and .true. for a call from newstart.F
58      INTEGER  tapedef  ! unit number to assign to 'run.def' file
59c
60c   local variables:
61c   ---------------
62
63      CHARACTER ch1*72,ch2*72,ch3*72,ch4*8 ! to store various strings
64      integer tapeerr ! unit number for error message
65      parameter (tapeerr=0)
66
67c     REAL clonn,clatt,alphaxx,alphayy
68c     LOGICAL  fxyhypbb
69      INTEGER ierr
70      REAL clonn,clatt,grossismxx,grossismyy
71      REAL dzoomxx,dzoomyy,tauxx,tauyy,temp
72      LOGICAL  fxyhypbb, ysinuss
73
74
75c   initialisations:
76c   ----------------
77 
78!      lunout=6
79
80c-----------------------------------------------------------------------
81c  Parametres de controle du run:
82c-----------------------------------------------------------------------
83
84
85!Initialisation des parametres "terrestres", qui ne concernent pas
86!le modele martien et ne sont donc plus lues dans "run.def"
87
88        anneeref=0
89        ! Note: anneref is a common in 'control.h'
90
91      OPEN(tapedef,file='run.def',status='old',form='formatted'
92     .     ,iostat=ierr)
93      CLOSE(tapedef) ! first call to getin will open the file
94
95      !lunout: default unit for the text outputs
96      lunout=6
97      CALL getin('lunout', lunout)
98      IF (lunout /= 5 .and. lunout /= 6) THEN
99        OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',
100     &       STATUS='unknown',FORM='formatted')
101      ENDIF
102
103      IF(ierr.EQ.0) THEN ! if file run.def is found
104        WRITE(lunout,*) "DEFRUN_NEW: reading file run.def"
105       
106        WRITE(lunout,*) ""
107        WRITE(lunout,*) "Number of days to run:"
108        nday=1 ! default value
109        call getin("nday",nday)
110        WRITE(lunout,*)" nday = ",nday
111
112        WRITE(lunout,*) ""
113        WRITE(lunout,*) "Number of dynamical steps per day:",
114     & "(should be a multiple of iperiod)"
115        day_step=960 ! default value
116        call getin("day_step",day_step)
117        WRITE(lunout,*)" day_step = ",day_step
118
119        WRITE(lunout,*) ""
120        WRITE(lunout,*) "periode pour le pas Matsuno (en pas)"
121        iperiod=5 ! default value
122        call getin("iperiod",iperiod)
123        WRITE(lunout,*)" iperiod = ",iperiod
124
125        WRITE(lunout,*) ""
126        WRITE(lunout,*) "periode de sortie des variables de ",
127     &  "controle (en pas)"
128        iconser=120 ! default value
129        call getin("iconser",iconser)
130        WRITE(lunout,*)" iconser = ",iconser
131
132        WRITE(lunout,*) ""
133        WRITE(lunout,*) "periode de la dissipation (en pas)"
134        dissip_period=5 ! default value
135        call getin("idissip",dissip_period)
136        ! if there is a "dissip_period" in run.def, it overrides "idissip"
137        call getin("dissip_period",dissip_period)
138        WRITE(lunout,*)" dissip_period = ",dissip_period
139
140ccc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
141ccc
142        WRITE(lunout,*) ""
143        WRITE(lunout,*) "choix de l'operateur de dissipation ",
144     & "(star ou  non star )"
145        lstardis=.true. ! default value
146        call getin("lstardis",lstardis)
147        WRITE(lunout,*)" lstardis = ",lstardis
148
149        WRITE(lunout,*) ""
150        WRITE(lunout,*) "avec ou sans coordonnee hybrides"
151        hybrid=.true. ! default value
152        call getin("hybrid",hybrid)
153        WRITE(lunout,*)" hybrid = ",hybrid
154
155        WRITE(lunout,*) ""
156        WRITE(lunout,*) "nombre d'iterations de l'operateur de ",
157     & "dissipation   gradiv "
158        nitergdiv=1 ! default value
159        call getin("nitergdiv",nitergdiv)
160        WRITE(lunout,*)" nitergdiv = ",nitergdiv
161
162        WRITE(lunout,*) ""
163        WRITE(lunout,*) "nombre d'iterations de l'operateur de ",
164     & "dissipation  nxgradrot"
165        nitergrot=2 ! default value
166        call getin("nitergrot",nitergrot)
167        WRITE(lunout,*)" nitergrot = ",nitergrot
168
169        WRITE(lunout,*) ""
170        WRITE(lunout,*) "nombre d'iterations de l'operateur de ",
171     & "dissipation  divgrad"
172        niterh=2 ! default value
173        call getin("niterh",niterh)
174        WRITE(lunout,*)" niterh = ",niterh
175
176        WRITE(lunout,*) ""
177        WRITE(lunout,*) "temps de dissipation des plus petites ",
178     & "long.d ondes pour u,v (gradiv)"
179        tetagdiv=4000. ! default value
180        call getin("tetagdiv",tetagdiv)
181        WRITE(lunout,*)" tetagdiv = ",tetagdiv
182
183        WRITE(lunout,*) ""
184        WRITE(lunout,*) "temps de dissipation des plus petites ",
185     & "long.d ondes pour u,v(nxgradrot)"
186        tetagrot=5000. ! default value
187        call getin("tetagrot",tetagrot)
188        WRITE(lunout,*)" tetagrot = ",tetagrot
189
190        WRITE(lunout,*) ""
191        WRITE(lunout,*) "temps de dissipation des plus petites ",
192     & "long.d ondes pour  h ( divgrad)"
193        tetatemp=5000. ! default value
194        call getin("tetatemp",tetatemp)
195        WRITE(lunout,*)" tetatemp = ",tetatemp
196
197        WRITE(lunout,*) ""
198        WRITE(lunout,*) "coefficient pour gamdissip"
199        coefdis=0. ! default value
200        call getin("coefdis",coefdis)
201        WRITE(lunout,*)" coefdis = ",coefdis
202c
203c    ...............................................................
204
205        WRITE(lunout,*) ""
206        WRITE(lunout,*) "choix du shema d'integration temporelle ",
207     & "(true==Matsuno ou false==Matsuno-leapfrog)"
208        purmats=.false. ! default value
209        call getin("purmats",purmats)
210        WRITE(lunout,*)" purmats = ",purmats
211
212        WRITE(lunout,*) ""
213        WRITE(lunout,*) "avec ou sans physique"
214!        physic=.true. ! default value
215!        call getin("physic",physic)
216!        WRITE(lunout,*)" physic = ",physic
217        iflag_phys=1 ! default value
218        call getin("iflag_phys",iflag_phys)
219        WRITE(lunout,*)" iflag_phys = ",iflag_phys
220
221        WRITE(lunout,*) ""
222        WRITE(lunout,*) "periode de la physique (en pas)"
223        iphysiq=20 ! default value
224        call getin("iphysiq",iphysiq)
225        WRITE(lunout,*)" iphysiq = ",iphysiq
226
227!        WRITE(lunout,*) ""
228!        WRITE(lunout,*) "choix d'une grille reguliere"
229!        grireg=.true.
230!        call getin("grireg",grireg)
231!        WRITE(lunout,*)" grireg = ",grireg
232
233ccc   .... P.Le Van, ajout le 03/01/96 pour l'ecriture phys ...
234c
235!        WRITE(lunout,*) ""
236!        WRITE(lunout,*) "frequence (en pas) de l'ecriture ",
237!     & "du fichier diagfi.nc"
238!        ecritphy=240
239!        call getin("ecritphy",ecritphy)
240!        WRITE(lunout,*)" ecritphy = ",ecritphy
241
242ccc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
243c     .........   (  modif  le 17/04/96 )   .........
244c
245        if (.not.etatinit ) then
246
247           clonn=63.
248           call getin("clon",clonn)
249           
250           IF( ABS(clon - clonn).GE. 0.001 )  THEN
251             PRINT *,' La valeur de clon passee par run.def est '
252     *       ,'differente de celle lue sur le fichier start '
253             STOP
254           ENDIF
255c
256c
257           clatt=0.
258           call getin("clat",clatt)
259 
260           IF( ABS(clat - clatt).GE. 0.001 )  THEN
261             PRINT *,' La valeur de clat passee par run.def est '
262     *       ,'differente de celle lue sur le fichier start '
263             STOP
264           ENDIF
265
266           grossismxx=1.0
267           call getin("grossismx",grossismxx)
268
269           if(grossismxx.eq.0) then 
270             write(*,*)
271             write(*,*)'ERREUR : dans run.def, grossismx =0'
272             write(*,*)'Attention a ne pas utiliser une version de'
273             write(*,*)'run.def avant le nouveau zoom LMDZ2.3 (06/2000)'
274             write(*,*)'(Il faut ajouter grossismx,dzoomx,etc... a la'
275             write(*,*)'place de alphax, alphay. cf. dyn3d). '
276             write(*,*)
277             stop
278           end if
279
280           IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
281             PRINT *,' La valeur de grossismx passee par run.def est '
282     *       ,'differente de celle lue sur le fichier  start =',
283     *        grossismx
284             if (grossismx.eq.0) then
285                  write(*,*) 'OK,Normal : c est un vieux start'
286     *             , 'd avant le nouveau zoom LMDZ2.3 (06/2000)'
287                 grossismx=grossismxx
288             else
289                   STOP
290             endif
291           ENDIF
292
293           grossismyy=1.0
294           call getin("grossismy",grossismyy)
295
296           IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
297             PRINT *,' La valeur de grossismy passee par run.def est '
298     *       ,'differente de celle lue sur le fichier  start =',
299     *        grossismy
300             if (grossismy.eq.0) then
301                  write(*,*) 'OK,Normal : c est un vieux start'
302     *             , 'd avant le nouveau zoom LMDZ2.3 (06/2000)'
303                 grossismy=grossismyy
304             else
305                   STOP
306             endif
307           ENDIF
308
309
310           IF( grossismx.LT.1. )  THEN
311             PRINT *,' ***  ATTENTION !! grossismx < 1 .   *** '
312             STOP
313           ELSE
314             alphax = 1. - 1./ grossismx
315           ENDIF
316
317           IF( grossismy.LT.1. )  THEN
318             PRINT *,' ***  ATTENTION !! grossismy < 1 .   *** '
319             STOP
320           ELSE
321             alphay = 1. - 1./ grossismy
322           ENDIF
323
324           PRINT *,' '
325           PRINT *,' --> In defrun: alphax alphay  ',alphax,alphay
326           PRINT *,' '
327c
328           fxyhypbb=.false.
329           call getin("fxyhypbb",fxyhypbb)
330 
331           IF( .NOT.fxyhypb )  THEN
332             IF( fxyhypbb )     THEN
333                PRINT *,' ********  PBS DANS  DEFRUN  ******** '
334                PRINT *,' *** fxyhypb lu sur le fichier start est F ',
335     *          'alors  qu il est  T  sur  run.def  ***'
336                STOP
337             ENDIF
338           ELSE
339             IF( .NOT.fxyhypbb )   THEN
340                PRINT *,' ********  PBS DANS  DEFRUN  ******** '
341                PRINT *,' ***  fxyhypb lu sur le fichier start est T ',
342     *         'alors  qu il est  F  sur  run.def  ****  '
343                STOP
344             ENDIF
345           ENDIF
346           dzoomxx=0.0
347           call getin("dzoomx",dzoomxx)
348
349           IF( fxyhypb )  THEN
350              IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
351                PRINT *,' La valeur de dzoomx passee par run.def est '
352     *          ,'differente de celle lue sur le fichier  start '
353                STOP
354              ENDIF
355           ENDIF
356
357           dzoomyy=0.0
358           call getin("dzoomy",dzoomyy)
359
360           IF( fxyhypb )  THEN
361              IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
362                PRINT *,' La valeur de dzoomy passee par run.def est '
363     *          ,'differente de celle lue sur le fichier  start '
364                STOP
365              ENDIF
366           ENDIF
367
368           tauxx=2.0
369           call getin("taux",tauxx)
370
371           tauyy=2.0
372           call getin("tauy",tauyy)
373
374           IF( fxyhypb )  THEN
375              IF( ABS(taux - tauxx).GE. 0.001 )  THEN
376                WRITE(6,*)' La valeur de taux passee par run.def est',
377     *             'differente de celle lue sur le fichier  start '
378                CALL ABORT
379              ENDIF
380
381              IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
382                WRITE(6,*)' La valeur de tauy passee par run.def est',
383     *          'differente de celle lue sur le fichier  start '
384                CALL ABORT
385              ENDIF
386           ENDIF
387 
388        ELSE    ! Below, case when etainit=.true.
389
390           WRITE(lunout,*) ""
391           WRITE(lunout,*) "longitude en degres du centre du zoom"
392           clon=63. ! default value
393           call getin("clon",clon)
394           WRITE(lunout,*)" clon = ",clon
395           
396c
397           WRITE(lunout,*) ""
398           WRITE(lunout,*) "latitude en degres du centre du zoom "
399           clat=0. ! default value
400           call getin("clat",clat)
401           WRITE(lunout,*)" clat = ",clat
402
403           WRITE(lunout,*) ""
404           WRITE(lunout,*) "facteur de grossissement du zoom,",
405     & " selon longitude"
406           grossismx=1.0 ! default value
407           call getin("grossismx",grossismx)
408           WRITE(lunout,*)" grossismx = ",grossismx
409
410           WRITE(lunout,*) ""
411           WRITE(lunout,*) "facteur de grossissement du zoom ,",
412     & " selon latitude"
413           grossismy=1.0 ! default value
414           call getin("grossismy",grossismy)
415           WRITE(lunout,*)" grossismy = ",grossismy
416
417           IF( grossismx.LT.1. )  THEN
418            PRINT *,' ***  ATTENTION !! grossismx < 1 .   *** '
419            STOP
420           ELSE
421             alphax = 1. - 1./ grossismx
422           ENDIF
423
424           IF( grossismy.LT.1. )  THEN
425             PRINT *,' ***  ATTENTION !! grossismy < 1 .   *** '
426             STOP
427           ELSE
428             alphay = 1. - 1./ grossismy
429           ENDIF
430
431           PRINT *,' Defrun  alphax alphay  ',alphax,alphay
432c
433           WRITE(lunout,*) ""
434           WRITE(lunout,*) "Fonction  f(y)  hyperbolique  si = .true.",
435     &  ", sinon  sinusoidale"
436           fxyhypb=.false. ! default value
437           call getin("fxyhypb",fxyhypb)
438           WRITE(lunout,*)" fxyhypb = ",fxyhypb
439
440           WRITE(lunout,*) ""
441           WRITE(lunout,*) "extension en longitude de la zone du zoom",
442     & " (fraction de la zone totale)"
443           dzoomx=0. ! default value
444           call getin("dzoomx",dzoomx)
445           WRITE(lunout,*)" dzoomx = ",dzoomx
446
447           WRITE(lunout,*) ""
448           WRITE(lunout,*) "extension en latitude de la zone du zoom",
449     & " (fraction de la zone totale)"
450           dzoomy=0. ! default value
451           call getin("dzoomy",dzoomy)
452           WRITE(lunout,*)" dzoomy = ",dzoomy
453
454           WRITE(lunout,*) ""
455           WRITE(lunout,*) "raideur du zoom en  X"
456           taux=2. ! default value
457           call getin("taux",taux)
458           WRITE(lunout,*)" taux = ",taux
459
460           WRITE(lunout,*) ""
461           WRITE(lunout,*) "raideur du zoom en  Y"
462           tauy=2.0 ! default value
463           call getin("tauy",tauy)
464           WRITE(lunout,*)" tauy = ",tauy
465
466        END IF ! of if (.not.etatinit )
467
468        WRITE(lunout,*) ""
469        WRITE(lunout,*) "Use a sponge layer?"
470        callsponge=.true. ! default value
471        call getin("callsponge",callsponge)
472        WRITE(lunout,*)" callsponge = ",callsponge
473
474        WRITE(lunout,*) ""
475        WRITE(lunout,*) "Sponge: number of layers over which",
476     &                    " sponge extends"
477        nsponge=3 ! default value
478        call getin("nsponge",nsponge)
479        WRITE(lunout,*)" nsponge = ",nsponge
480
481        WRITE(lunout,*)""
482        WRITE(lunout,*)"Sponge mode: (forcing is towards ..."
483        WRITE(lunout,*)"  over upper nsponge layers)"
484        WRITE(lunout,*)"  0: (h=hmean,u=v=0)"
485        WRITE(lunout,*)"  1: (h=hmean,u=umean,v=0)"
486        WRITE(lunout,*)"  2: (h=hmean,u=umean,v=vmean)"
487        mode_sponge=2 ! default value
488        call getin("mode_sponge",mode_sponge)
489        WRITE(lunout,*)" mode_sponge = ",mode_sponge
490
491        WRITE(lunout,*) ""
492        WRITE(lunout,*) "Sponge: characteristic time scale tetasponge"
493        WRITE(lunout,*) "(seconds) at topmost layer (time scale then "
494        WRITE(lunout,*) " doubles with decreasing layer index)."
495        tetasponge=50000.0
496        call getin("tetasponge",tetasponge)
497        WRITE(lunout,*)" tetasponge = ",tetasponge
498
499
500      WRITE(lunout,*) '-----------------------------------------------'
501      WRITE(lunout,*) ' '
502      WRITE(lunout,*) ' '
503c
504
505c       Unlike on Earth (cf LMDZ2.2) , always a regular grid on Mars :
506        ysinus = .false. !Mars Mettre a jour
507
508
509      WRITE(lunout,*) '-----------------------------------------------'
510      WRITE(lunout,*) ' '
511      WRITE(lunout,*) ' '
512cc
513      ELSE
514        write(tapeerr,*) ' WHERE IS run.def ? WE NEED IT !!!!!!!!!!!!!!'
515        stop
516      ENDIF ! of IF(ierr.eq.0)
517
518c     Test sur le zoom
519
520      if((grossismx.eq.1).and.(grossismy.eq.1)) then 
521c        Pas de zoom :
522         write(lunout,*) 'No zoom ? -> fxyhypb set to False'
523     &   ,'           (It runs better that way)'
524         fxyhypb = .false.
525      else     
526c        Avec Zoom
527         if (.not.fxyhypb) stop 'With zoom, fxyhypb should be set to T
528     &in run.def for this version... -> STOP ! '     
529      end if
530#else
531      write(*,*) "defrun_new should not be used in parallel mode!"
532      stop
533#endif
534! of #ifndef CPP_PARA
535      END
Note: See TracBrowser for help on using the repository browser.