source: trunk/LMDZ.GENERIC/libf/dyn3d/defrun_new.F @ 1243

Last change on this file since 1243 was 1216, checked in by emillour, 11 years ago

Generic model:
Major cleanup, in order to ease the use of LMDZ.GENERIC with (parallel) dynamics
in LMDZ.COMMON: (NB: this will break LMDZ.UNIVERSAL, which should be thrashed
in the near future)

  • Updated makegcm_* scripts (and makdim) and added the "-full" (to enforce full recomputation of the model) option
  • In dyn3d: converted control.h to module control_mod.F90 and converted iniadvtrac.F to module infotrac.F90
  • Added module mod_const_mpi.F90 in dyn3d (not used in serial mode)
  • Rearanged input/outputs routines everywhere to handle serial/MPI cases. physdem.F => phyredem.F90 , phyetat0.F => phyetat0.F90 ; all read/write routines for startfi files are gathered in module iostart.F90
  • added parallelism related routines init_phys_lmdz.F90, comgeomphy.F90, dimphy.F90, iniphysiq.F90, mod_grid_phy_lmdz.F90, mod_phys_lmdz_mpi_data.F90, mod_phys_lmdz_mpi_transfert.F90, mod_phys_lmdz_omp_data.F90, mod_phys_lmdz_omp_transfert.F90, mod_phys_lmdz_para.F90, mod_phys_lmdz_transfert_para.F90 in phymars and mod_const_mpi.F90 in dyn3d (for compliance with parallelism)
  • added created generic routines 'planetwide_maxval' and 'planetwide_minval', in module "planetwide_mod", that enable obtaining the max and min of a field over the whole planet. This should be further imroved with computation of means (possibly area weighed), etc.

EM

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