source: LMDZ6/trunk/libf/dyn3dmem/conf_gcm.F90 @ 5300

Last change on this file since 5300 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 34.8 KB
RevLine 
[2142]1
[1673]2! $Id$
[2142]3
[2221]4SUBROUTINE conf_gcm( tapedef, etatinit )
[2142]5
[5282]6  USE iniprint_mod_h
[5280]7  USE comdissnew_mod_h
[2142]8  USE control_mod
[4100]9  USE IOIPSL
[5267]10
[4100]11  USE misc_mod
12  USE mod_filtre_fft, ONLY: use_filtre_fft
13  USE mod_filtre_fft_loc, ONLY: use_filtre_fft_loc=>use_filtre_fft
14  USE mod_hallo, ONLY: use_mpi_alloc
15  USE infotrac, ONLY: type_trac
16  USE assert_m, ONLY: assert
[2597]17  USE comconst_mod, ONLY: dissip_deltaz, dissip_factz, dissip_zref, &
18                          iflag_top_bound, mode_top_bound, tau_top_bound, &
[4519]19                          ngroup, maxlatfilter
[2603]20  USE logic_mod, ONLY: fxyhypb, iflag_phys, ok_etat0, ok_gradsfile, &
21                       ok_guide, ok_limit, ok_strato, purmats, read_start, &
[4996]22                       ysinus, read_orop, adv_qsat_liq
[2598]23  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
24                       alphax,alphay,taux,tauy
[4608]25  USE temps_mod, ONLY: calend, year_len, offline_time
[1699]26
[5271]27  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
[5285]28USE paramet_mod_h
[5271]29IMPLICIT NONE
[2142]30  !-----------------------------------------------------------------------
31  !     Auteurs :   L. Fairhead , P. Le Van  .
[1632]32
[2142]33  !     Arguments :
[1632]34
[2142]35  !     tapedef   :
[5271]36  !     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
[2142]37  !     -metres  du zoom  avec  celles lues sur le fichier start .
[1632]38
[2221]39  LOGICAL,INTENT(IN) :: etatinit
40  INTEGER,INTENT(IN) :: tapedef
[2141]41
[2142]42  !   Declarations :
43  !   --------------
[5271]44
[5272]45
[2142]46
47  !   local:
48  !   ------
49
50  CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
51  REAL clonn,clatt,grossismxx,grossismyy
52  REAL dzoomxx,dzoomyy, tauxx,tauyy
53  LOGICAL  fxyhypbb, ysinuss
54  INTEGER i
[4100]55  CHARACTER(len=*), PARAMETER :: modname="conf_gcm"
56  CHARACTER(len=80) :: abort_message
[1734]57#ifdef CPP_OMP
[4100]58  INTEGER, EXTERNAL :: OMP_GET_NUM_THREADS
[1734]59#endif
60
[2142]61  !  -------------------------------------------------------------------
[1734]62
[2142]63  !       .........     Version  du 29/04/97       ..........
[1632]64
[2142]65  !   Nouveaux parametres nitergdiv,nitergrot,niterh,tetagdiv,tetagrot,
66  !      tetatemp   ajoutes  pour la dissipation   .
[1632]67
[2142]68  !   Autre parametre ajoute en fin de liste de tapedef : ** fxyhypb **
[1632]69
[2142]70  !  Si fxyhypb = .TRUE. , choix de la fonction a derivee tangente hyperb.
71  !    Sinon , choix de fxynew  , a derivee sinusoidale  ..
[1632]72
[2142]73  !   ......  etatinit = . TRUE. si defrun  est appele dans ETAT0_LMD  ou
74  !         LIMIT_LMD  pour l'initialisation de start.dat (dic) et
75  !                de limit.dat ( dic)                        ...........
76  !           Sinon  etatinit = . FALSE .
[1632]77
[2142]78  !   Donc etatinit = .F.  si on veut comparer les valeurs de  grossismx ,
79  !    grossismy,clon,clat, fxyhypb  lues sur  le fichier  start  avec
80  !   celles passees  par run.def ,  au debut du gcm, apres l'appel a
81  !    lectba . 
82  !   Ces parmetres definissant entre autres la grille et doivent etre
83  !   pareils et coherents , sinon il y aura  divergence du gcm .
[1632]84
[2142]85  !-----------------------------------------------------------------------
86  !   initialisations:
87  !   ----------------
[2083]88
[2142]89  !Config  Key  = lunout
90  !Config  Desc = unite de fichier pour les impressions
91  !Config  Def  = 6
92  !Config  Help = unite de fichier pour les impressions
93  !Config         (defaut sortie standard = 6)
94  lunout=6
95  CALL getin('lunout', lunout)
96  IF (lunout /= 5 .and. lunout /= 6) THEN
97     OPEN(UNIT=lunout,FILE='lmdz.out_0000',ACTION='write',  &
98          STATUS='unknown',FORM='formatted')
99  ENDIF
[1632]100
[2142]101  adjust=.false.
[4100]102  CALL getin('adjust',adjust)
[1673]103
[2142]104#ifdef CPP_OMP
105  ! adjust=y not implemented in case of OpenMP threads...
106  !$OMP PARALLEL
[4100]107  IF ((OMP_GET_NUM_THREADS()>1).and.adjust) then
[2142]108     write(lunout,*)'conf_gcm: Error, adjust should be set to n' &
109          ,' when running with OpenMP threads'
110     abort_message = 'Wrong value for adjust'
[4100]111     CALL abort_gcm(modname,abort_message,1)
112  ENDIF
[2142]113  !$OMP END PARALLEL         
114#endif
[1632]115
[2142]116  itaumax=0
[4100]117  CALL getin('itaumax',itaumax);
118  IF (itaumax<=0) itaumax=HUGE(itaumax)
[1657]119
[2142]120  !Config  Key  = prt_level
[5267]121  !Config  Desc = niveau d'impressions de d�bogage
[2142]122  !Config  Def  = 0
[5267]123  !Config  Help = Niveau d'impression pour le d�bogage
[2142]124  !Config         (0 = minimum d'impression)
125  prt_level = 0
126  CALL getin('prt_level',prt_level)
[1632]127
[2142]128  !-----------------------------------------------------------------------
129  !  Parametres de controle du run:
130  !-----------------------------------------------------------------------
131  !Config  Key  = planet_type
132  !Config  Desc = planet type ("earth", "mars", "venus", ...)
133  !Config  Def  = earth
134  !Config  Help = this flag sets the type of atymosphere that is considered
135  planet_type="earth"
136  CALL getin('planet_type',planet_type)
[1632]137
[2142]138  !Config  Key  = calend
139  !Config  Desc = type de calendrier utilise
140  !Config  Def  = earth_360d
141  !Config  Help = valeur possible: earth_360d, earth_365d, earth_366d
142  !Config         
143  calend = 'earth_360d'
[3579]144! initialize year_len for aquaplanets and 1D
[2142]145  CALL getin('calend', calend)
[4100]146  IF (calend == 'earth_360d') THEN
147    year_len=360
148  ELSE IF (calend == 'earth_365d') THEN
149    year_len=365
150  ELSE IF (calend == 'earth_366d') THEN
151    year_len=366
152  ELSE
153    year_len=1
154  ENDIF
[1632]155
[2142]156  !Config  Key  = dayref
157  !Config  Desc = Jour de l'etat initial
158  !Config  Def  = 1
159  !Config  Help = Jour de l'etat initial ( = 350  si 20 Decembre ,
160  !Config         par expl. ,comme ici ) ... A completer
161  dayref=1
162  CALL getin('dayref', dayref)
[1632]163
[2142]164  !Config  Key  = anneeref
165  !Config  Desc = Annee de l'etat initial
166  !Config  Def  = 1998
167  !Config  Help = Annee de l'etat  initial
168  !Config         (   avec  4  chiffres   ) ... A completer
169  anneeref = 1998
170  CALL getin('anneeref',anneeref)
[1632]171
[2142]172  !Config  Key  = raz_date
173  !Config  Desc = Remise a zero de la date initiale
174  !Config  Def  = 0 (pas de remise a zero)
175  !Config  Help = Remise a zero de la date initiale
176  !Config         0 pas de remise a zero, on garde la date du fichier restart
177  !Config         1 prise en compte de la date de gcm.def avec remise a zero
178  !Config         des compteurs de pas de temps
179  raz_date = 0
180  CALL getin('raz_date', raz_date)
[1632]181
[2142]182  !Config  Key  = resetvarc
183  !Config  Desc = Reinit des variables de controle
184  !Config  Def  = n
185  !Config  Help = Reinit des variables de controle
186  resetvarc = .false.
187  CALL getin('resetvarc',resetvarc)
[1632]188
[2142]189  !Config  Key  = nday
190  !Config  Desc = Nombre de jours d'integration
191  !Config  Def  = 10
192  !Config  Help = Nombre de jours d'integration
193  !Config         ... On pourait aussi permettre des mois ou des annees !
194  nday = 10
195  CALL getin('nday',nday)
[1632]196
[2142]197  !Config  Key  = starttime
198  !Config  Desc = Heure de depart de la simulation
199  !Config  Def  = 0
200  !Config  Help = Heure de depart de la simulation
201  !Config         en jour
202  starttime = 0
203  CALL getin('starttime',starttime)
[1632]204
[2142]205  !Config  Key  = day_step
206  !Config  Desc = nombre de pas par jour
207  !Config  Def  = 240
208  !Config  Help = nombre de pas par jour (multiple de iperiod) (
209  !Config          ici pour  dt = 1 min )
210  day_step = 240
211  CALL getin('day_step',day_step)
[1632]212
[2142]213  !Config  Key  = nsplit_phys
214  nsplit_phys = 1
215  CALL getin('nsplit_phys',nsplit_phys)
[1632]216
[2142]217  !Config  Key  = iperiod
218  !Config  Desc = periode pour le pas Matsuno
219  !Config  Def  = 5
220  !Config  Help = periode pour le pas Matsuno (en pas de temps)
221  iperiod = 5
222  CALL getin('iperiod',iperiod)
[1632]223
[2142]224  !Config  Key  = iapp_tracvl
225  !Config  Desc = frequence du groupement des flux
226  !Config  Def  = iperiod
227  !Config  Help = frequence du groupement des flux (en pas de temps)
228  iapp_tracvl = iperiod
229  CALL getin('iapp_tracvl',iapp_tracvl)
[1632]230
[2142]231  !Config  Key  = iconser
232  !Config  Desc = periode de sortie des variables de controle
233  !Config  Def  = 240 
234  !Config  Help = periode de sortie des variables de controle
235  !Config         (En pas de temps)
236  iconser = 240 
237  CALL getin('iconser', iconser)
[1632]238
[2142]239  !Config  Key  = iecri
240  !Config  Desc = periode d'ecriture du fichier histoire
241  !Config  Def  = 1
242  !Config  Help = periode d'ecriture du fichier histoire (en jour)
243  iecri = 1
244  CALL getin('iecri',iecri)
[1632]245
[2142]246  !Config  Key  = periodav
247  !Config  Desc = periode de stockage fichier histmoy
248  !Config  Def  = 1
249  !Config  Help = periode de stockage fichier histmoy (en jour)
250  periodav = 1.
251  CALL getin('periodav',periodav)
[1632]252
[2142]253  !Config  Key  = output_grads_dyn
254  !Config  Desc = output dynamics diagnostics in 'dyn.dat' file
255  !Config  Def  = n
256  !Config  Help = output dynamics diagnostics in Grads-readable 'dyn.dat' file
257  output_grads_dyn=.false.
258  CALL getin('output_grads_dyn',output_grads_dyn)
[1632]259
[2142]260  !Config  Key  = dissip_period
261  !Config  Desc = periode de la dissipation
262  !Config  Def  = 0
263  !Config  Help = periode de la dissipation
264  !Config  dissip_period=0 => la valeur sera calcule dans inidissip       
265  !Config  dissip_period>0 => on prend cette valeur
266  dissip_period = 0
267  CALL getin('dissip_period',dissip_period)
[1632]268
[2142]269  !cc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
270  !cc
[1632]271
[2142]272  !Config  Key  = lstardis
273  !Config  Desc = choix de l'operateur de dissipation
274  !Config  Def  = y
275  !Config  Help = choix de l'operateur de dissipation
276  !Config         'y' si on veut star et 'n' si on veut non-start !
277  !Config         Moi y en a pas comprendre !
278  lstardis = .TRUE.
279  CALL getin('lstardis',lstardis)
[1632]280
[2142]281  !Config  Key  = nitergdiv
282  !Config  Desc = Nombre d'iteration de gradiv
283  !Config  Def  = 1
284  !Config  Help = nombre d'iterations de l'operateur de dissipation
285  !Config         gradiv
286  nitergdiv = 1
287  CALL getin('nitergdiv',nitergdiv)
[1632]288
[2142]289  !Config  Key  = nitergrot
290  !Config  Desc = nombre d'iterations de nxgradrot
291  !Config  Def  = 2
292  !Config  Help = nombre d'iterations de l'operateur de dissipation 
293  !Config         nxgradrot
294  nitergrot = 2
295  CALL getin('nitergrot',nitergrot)
[1793]296
[2142]297  !Config  Key  = niterh
298  !Config  Desc = nombre d'iterations de divgrad
299  !Config  Def  = 2
300  !Config  Help = nombre d'iterations de l'operateur de dissipation
301  !Config         divgrad
302  niterh = 2
303  CALL getin('niterh',niterh)
[1793]304
[2142]305  !Config  Key  = tetagdiv
306  !Config  Desc = temps de dissipation pour div
307  !Config  Def  = 7200
308  !Config  Help = temps de dissipation des plus petites longeur
309  !Config         d'ondes pour u,v (gradiv)
310  tetagdiv = 7200.
311  CALL getin('tetagdiv',tetagdiv)
[1632]312
[2142]313  !Config  Key  = tetagrot
314  !Config  Desc = temps de dissipation pour grad
315  !Config  Def  = 7200
316  !Config  Help = temps de dissipation des plus petites longeur
317  !Config         d'ondes pour u,v (nxgradrot)
318  tetagrot = 7200.
319  CALL getin('tetagrot',tetagrot)
[1632]320
[2142]321  !Config  Key  = tetatemp
322  !Config  Desc = temps de dissipation pour h
323  !Config  Def  = 7200
324  !Config  Help =  temps de dissipation des plus petites longeur
325  !Config         d'ondes pour h (divgrad)   
326  tetatemp  = 7200.
327  CALL getin('tetatemp',tetatemp )
[1632]328
[2142]329  ! Parametres controlant la variation sur la verticale des constantes de
330  ! dissipation.
331  ! Pour le moment actifs uniquement dans la version a 39 niveaux
332  ! avec ok_strato=y
[1632]333
[2142]334  dissip_factz=4.
335  dissip_deltaz=10.
336  dissip_zref=30.
337  CALL getin('dissip_factz',dissip_factz )
338  CALL getin('dissip_deltaz',dissip_deltaz )
339  CALL getin('dissip_zref',dissip_zref )
[1632]340
[4519]341
342  !maxlatfilter
343  maxlatfilter = -1.0
344  CALL getin('maxlatfilter',maxlatfilter)
345  if (maxlatfilter > 90) &
346       call abort_gcm("conf_gcm", 'maxlatfilter should be <=90', 1)
347 
348
[2442]349  ! ngroup
350  ngroup=3
351  CALL getin('ngroup',ngroup)
[4100]352  IF (mod(iim, 2**ngroup) /= 0) &
[3802]353       call abort_gcm("conf_gcm", 'iim must be multiple of 2**ngroup', 1)
[4100]354  IF (2**ngroup > jjm + 1) &
[3802]355       call abort_gcm("conf_gcm", '2**ngroup must be <= jjm + 1', 1)
[2442]356
357  ! mode_top_bound : fields towards which sponge relaxation will be done:
[2142]358  ! top_bound sponge: only active if ok_strato=.true. and iflag_top_bound!=0
359  !                   iflag_top_bound=0 for no sponge
360  !                   iflag_top_bound=1 for sponge over 4 topmost layers
361  !                   iflag_top_bound=2 for sponge from top to ~1% of top layer pressure
362  iflag_top_bound=1
363  CALL getin('iflag_top_bound',iflag_top_bound)
[4100]364  IF (iflag_top_bound < 0 .or. iflag_top_bound > 2) &
[4055]365       call abort_gcm("conf_gcm", 'iflag_top_bound must be 0, 1 or 2', 1)
[1632]366
[2142]367  ! mode_top_bound : fields towards which sponge relaxation will be done:
368  !                  mode_top_bound=0: no relaxation
369  !                  mode_top_bound=1: u and v relax towards 0
370  !                  mode_top_bound=2: u and v relax towards their zonal mean
371  !                  mode_top_bound=3: u,v and pot. temp. relax towards their zonal mean
372  mode_top_bound=3
373  CALL getin('mode_top_bound',mode_top_bound)
[1632]374
[2142]375  ! top_bound sponge : inverse of charactericstic relaxation time scale for sponge
376  tau_top_bound=1.e-5
377  CALL getin('tau_top_bound',tau_top_bound)
[1632]378
[2142]379  !Config  Key  = coefdis
380  !Config  Desc = coefficient pour gamdissip
381  !Config  Def  = 0
382  !Config  Help = coefficient pour gamdissip 
383  coefdis = 0.
384  CALL getin('coefdis',coefdis)
[1632]385
[2142]386  !Config  Key  = purmats
387  !Config  Desc = Schema d'integration
388  !Config  Def  = n
389  !Config  Help = Choix du schema d'integration temporel.
390  !Config         y = pure Matsuno sinon c'est du Matsuno-leapfrog
391  purmats = .FALSE.
392  CALL getin('purmats',purmats)
[2141]393
[2142]394  !Config  Key  = ok_guide
395  !Config  Desc = Guidage
396  !Config  Def  = n
397  !Config  Help = Guidage
398  ok_guide = .FALSE.
399  CALL getin('ok_guide',ok_guide)
[1632]400
[4100]401  IF (ok_guide .and. adjust) call abort_gcm("conf_gcm", &
[2142]402       "adjust does not work with ok_guide", 1)
[1632]403
[2142]404  !Config  Key  =  read_start
405  !Config  Desc = Initialize model using a 'start.nc' file
406  !Config  Def  = y
407  !Config  Help = y: intialize dynamical fields using a 'start.nc' file
408  !               n: fields are initialized by 'iniacademic' routine
409  read_start= .true.
410  CALL getin('read_start',read_start)
[1632]411
[2142]412  !Config  Key  = iflag_phys
413  !Config  Desc = Avec ls physique
414  !Config  Def  = 1
415  !Config  Help = Permet de faire tourner le modele sans
416  !Config         physique.
417  iflag_phys = 1
418  CALL getin('iflag_phys',iflag_phys)
[1632]419
[2142]420  !Config  Key  =  iphysiq
421  !Config  Desc = Periode de la physique
422  !Config  Def  = 5
423  !Config  Help = Periode de la physique en pas de temps de la dynamique.
424  iphysiq = 5
425  CALL getin('iphysiq', iphysiq)
[1632]426
[2142]427  !Config  Key  = ip_ebil_dyn
428  !Config  Desc = PRINT level for energy conserv. diag.
429  !Config  Def  = 0
430  !Config  Help = PRINT level for energy conservation diag. ;
431  !               les options suivantes existent :
432  !Config         0 pas de print
433  !Config         1 pas de print
434  !Config         2 print,
435  ip_ebil_dyn = 0
436  CALL getin('ip_ebil_dyn',ip_ebil_dyn)
437
438  !cc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
439  !     .........   (  modif  le 17/04/96 )   .........
440
441  test_etatinit: IF (.not. etatinit) then
442     !Config  Key  = clon
443     !Config  Desc = centre du zoom, longitude
444     !Config  Def  = 0
445     !Config  Help = longitude en degres du centre
446     !Config         du zoom
447     clonn = 0.
448     CALL getin('clon',clonn)
449
450     !Config  Key  = clat
451     !Config  Desc = centre du zoom, latitude
452     !Config  Def  = 0
453     !Config  Help = latitude en degres du centre du zoom
454     !Config         
455     clatt = 0.
456     CALL getin('clat',clatt)
457
458     IF( ABS(clat - clatt).GE. 0.001 )  THEN
459        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def', &
460             ' est differente de celle lue sur le fichier  start '
[4469]461        CALL abort_gcm("conf_gcm","stopped",1)
[2142]462     ENDIF
[1632]463
[2142]464     !Config  Key  = grossismx
465     !Config  Desc = zoom en longitude
466     !Config  Def  = 1.0
467     !Config  Help = facteur de grossissement du zoom,
468     !Config         selon la longitude
469     grossismxx = 1.0
470     CALL getin('grossismx',grossismxx)
[1632]471
[2142]472     IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
473        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ', &
474             'run.def est differente de celle lue sur le fichier  start '
[4469]475        CALL abort_gcm("conf_gcm","stopped",1)
476      ENDIF
[1632]477
[2142]478     !Config  Key  = grossismy
479     !Config  Desc = zoom en latitude
480     !Config  Def  = 1.0
481     !Config  Help = facteur de grossissement du zoom,
482     !Config         selon la latitude
483     grossismyy = 1.0
484     CALL getin('grossismy',grossismyy)
485
486     IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
487        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ', &
488             'run.def est differente de celle lue sur le fichier  start '
[4469]489        CALL abort_gcm("conf_gcm","stopped",1)
[2142]490     ENDIF
[1632]491
[2142]492     IF( grossismx.LT.1. )  THEN
493        write(lunout,*) &
494             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
[4469]495        CALL abort_gcm("conf_gcm","stopped",1)
[2142]496     ELSE
497        alphax = 1. - 1./ grossismx
498     ENDIF
[1632]499
[2142]500     IF( grossismy.LT.1. )  THEN
501        write(lunout,*) &
502             'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
[4469]503        CALL abort_gcm("conf_gcm","stopped",1)
[2142]504     ELSE
505        alphay = 1. - 1./ grossismy
506     ENDIF
[1632]507
[2142]508     write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
[1632]509
[2142]510     !    alphax et alphay sont les anciennes formulat. des grossissements
[1632]511
[2142]512     !Config  Key  = fxyhypb
513     !Config  Desc = Fonction  hyperbolique
514     !Config  Def  = y
515     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
516     !Config         sinon  sinusoidale
517     fxyhypbb = .TRUE.
518     CALL getin('fxyhypb',fxyhypbb)
[1632]519
[2142]520     IF( .NOT.fxyhypb )  THEN
521        IF( fxyhypbb )     THEN
522           write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
523           write(lunout,*)' *** fxyhypb lu sur le fichier start est ', &
524                'F alors  qu il est  T  sur  run.def  ***'
[4469]525           CALL abort_gcm("conf_gcm","stopped",1)
[2142]526        ENDIF
527     ELSE
528        IF( .NOT.fxyhypbb )   THEN
529           write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
530           write(lunout,*)' ***  fxyhypb lu sur le fichier start est ', &
531                'T alors  qu il est  F  sur  run.def  ****  '
[4469]532           CALL abort_gcm("conf_gcm","stopped",1)
[2142]533        ENDIF
534     ENDIF
[1632]535
[2142]536     !Config  Key  = dzoomx
537     !Config  Desc = extension en longitude
538     !Config  Def  = 0
539     !Config  Help = extension en longitude  de la zone du zoom 
540     !Config         ( fraction de la zone totale)
541     dzoomxx = 0.0
542     CALL getin('dzoomx',dzoomxx)
[1632]543
[2142]544     IF( fxyhypb )  THEN
545        IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
546           write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ', &
547                'run.def est differente de celle lue sur le fichier  start '
[4469]548           CALL abort_gcm("conf_gcm","stopped",1)
[2142]549        ENDIF
550     ENDIF
[1632]551
[2142]552     !Config  Key  = dzoomy
553     !Config  Desc = extension en latitude
554     !Config  Def  = 0
555     !Config  Help = extension en latitude de la zone  du zoom 
556     !Config         ( fraction de la zone totale)
557     dzoomyy = 0.0
558     CALL getin('dzoomy',dzoomyy)
[1632]559
[2142]560     IF( fxyhypb )  THEN
561        IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
562           write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ', &
563                'run.def est differente de celle lue sur le fichier  start '
[4469]564           CALL abort_gcm("conf_gcm","stopped",1)
[2142]565        ENDIF
566     ENDIF
[1632]567
[2142]568     !Config  Key  = taux
569     !Config  Desc = raideur du zoom en  X
570     !Config  Def  = 3
571     !Config  Help = raideur du zoom en  X
572     tauxx = 3.0
573     CALL getin('taux',tauxx)
[1632]574
[2142]575     IF( fxyhypb )  THEN
576        IF( ABS(taux - tauxx).GE. 0.001 )  THEN
577           write(lunout,*)'conf_gcm: La valeur de taux passee par ', &
578                'run.def est differente de celle lue sur le fichier  start '
[4469]579           CALL abort_gcm("conf_gcm","stopped",1)
[2142]580        ENDIF
581     ENDIF
[1632]582
[2142]583     !Config  Key  = tauyy
584     !Config  Desc = raideur du zoom en  Y
585     !Config  Def  = 3
586     !Config  Help = raideur du zoom en  Y
587     tauyy = 3.0
588     CALL getin('tauy',tauyy)
[1632]589
[2142]590     IF( fxyhypb )  THEN
591        IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
592           write(lunout,*)'conf_gcm: La valeur de tauy passee par ', &
593                'run.def est differente de celle lue sur le fichier  start '
[4469]594        CALL abort_gcm("conf_gcm","stopped",1)
[2142]595        ENDIF
596     ENDIF
[1632]597
[2142]598     !c
599     IF( .NOT.fxyhypb  )  THEN
[1632]600
[2142]601        !Config  Key  = ysinus
602        !Config  IF   = !fxyhypb
603        !Config  Desc = Fonction en Sinus
604        !Config  Def  = y
605        !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
606        !Config         sinon y = latit.
607        ysinuss = .TRUE.
608        CALL getin('ysinus',ysinuss)
609
[1632]610        IF( .NOT.ysinus )  THEN
[2142]611           IF( ysinuss )     THEN
612              write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
613              write(lunout,*)' *** ysinus lu sur le fichier start est F', &
614                   ' alors  qu il est  T  sur  run.def  ***'
[4469]615              CALL abort_gcm("conf_gcm","stopped",1)
[2142]616           ENDIF
[1632]617        ELSE
[2142]618           IF( .NOT.ysinuss )   THEN
619              write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
620              write(lunout,*)' *** ysinus lu sur le fichier start est T', &
621                   ' alors  qu il est  F  sur  run.def  ****  '
[4469]622              CALL abort_gcm("conf_gcm","stopped",1)
[2142]623           ENDIF
[1632]624        ENDIF
[2142]625     ENDIF ! of IF( .NOT.fxyhypb  )
[1632]626
[2142]627     !Config  Key  = offline
[4608]628     !Config  Desc = ecriture des flux de masse
[2142]629     !Config  Def  = n
[4608]630     !Config  Help = Permet de sortir les flux de masse sur la grille plev
[2142]631     offline = .FALSE.
632     CALL getin('offline',offline)
[4608]633
634     !Config Key  = offline_time
635     !Config Desc =  Choix des frequences de stockage pour le offline
636     !Config Def  = 8
637     !Config Help = offline_time=12     ! stockage toutes les 2h=1jour/12
638     !Config Help = offline_time=8      ! stockage toutes les 3h=1jour/8
639     offline_time = 8
640     CALL getin('offline_time',offline_time)
641
[2142]642     IF (offline .AND. adjust) THEN
643        WRITE(lunout,*)  &
644             'WARNING : option offline does not work with adjust=y :'
645        WRITE(lunout,*) 'the files defstoke.nc, fluxstoke.nc ',  &
646             'and fluxstokev.nc will not be created'
647        WRITE(lunout,*)  &
648             'only the file phystoke.nc will still be created '
[4100]649     ENDIF
[1632]650
[2142]651     !Config  Key  = type_trac
652     !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
653     !Config  Def  = lmdz
654     !Config  Help =
655     !Config         'lmdz' = pas de couplage, pur LMDZ
656     !Config         'inca' = model de chime INCA
657     !Config         'repr' = model de chime REPROBUS
658     type_trac = 'lmdz'
659     CALL getin('type_trac',type_trac)
[1632]660
[4996]661
662     !Config  Key  = adv_qsat_liq
663     !Config  Desc = option for qsat calculation in the dynamics
664     !Config  Def  = n
665     !Config  Help = controls which phase is considered for qsat calculation
666     !Config         
667     adv_qsat_liq = .FALSE.
668     CALL getin('adv_qsat_liq',adv_qsat_liq)
669
[2142]670     !Config  Key  = ok_dynzon
671     !Config  Desc = calcul et sortie des transports
672     !Config  Def  = n
673     !Config  Help = Permet de mettre en route le calcul des transports
674     !Config         
675     ok_dynzon = .FALSE.
676     CALL getin('ok_dynzon',ok_dynzon)
[1657]677
[2142]678     !Config  Key  = ok_dyn_ins
679     !Config  Desc = sorties instantanees dans la dynamique
680     !Config  Def  = n
681     !Config  Help =
682     !Config         
683     ok_dyn_ins = .FALSE.
684     CALL getin('ok_dyn_ins',ok_dyn_ins)
[1632]685
[2142]686     !Config  Key  = ok_dyn_ave
687     !Config  Desc = sorties moyennes dans la dynamique
688     !Config  Def  = n
689     !Config  Help =
690     !Config         
691     ok_dyn_ave = .FALSE.
692     CALL getin('ok_dyn_ave',ok_dyn_ave)
[1632]693
[4146]694     !Config  Key  = ok_dyn_xios
695     !Config  Desc = sorties moyennes dans la dynamique
696     !Config  Def  = n
697     !Config  Help =
698     !Config         
699     ok_dyn_xios = .FALSE.
700     CALL getin('ok_dyn_xios',ok_dyn_xios)
701
[2142]702     write(lunout,*)' #########################################'
703     write(lunout,*)' Configuration des parametres du gcm: '
704     write(lunout,*)' planet_type = ', planet_type
705     write(lunout,*)' calend = ', calend
706     write(lunout,*)' dayref = ', dayref
707     write(lunout,*)' anneeref = ', anneeref
708     write(lunout,*)' nday = ', nday
709     write(lunout,*)' day_step = ', day_step
710     write(lunout,*)' iperiod = ', iperiod
711     write(lunout,*)' nsplit_phys = ', nsplit_phys
712     write(lunout,*)' iconser = ', iconser
713     write(lunout,*)' iecri = ', iecri
714     write(lunout,*)' periodav = ', periodav
715     write(lunout,*)' output_grads_dyn = ', output_grads_dyn
716     write(lunout,*)' dissip_period = ', dissip_period
717     write(lunout,*)' lstardis = ', lstardis
718     write(lunout,*)' nitergdiv = ', nitergdiv
719     write(lunout,*)' nitergrot = ', nitergrot
720     write(lunout,*)' niterh = ', niterh
721     write(lunout,*)' tetagdiv = ', tetagdiv
722     write(lunout,*)' tetagrot = ', tetagrot
723     write(lunout,*)' tetatemp = ', tetatemp
724     write(lunout,*)' coefdis = ', coefdis
725     write(lunout,*)' purmats = ', purmats
726     write(lunout,*)' read_start = ', read_start
727     write(lunout,*)' iflag_phys = ', iflag_phys
728     write(lunout,*)' iphysiq = ', iphysiq
729     write(lunout,*)' clonn = ', clonn
730     write(lunout,*)' clatt = ', clatt
731     write(lunout,*)' grossismx = ', grossismx
732     write(lunout,*)' grossismy = ', grossismy
733     write(lunout,*)' fxyhypbb = ', fxyhypbb
734     write(lunout,*)' dzoomxx = ', dzoomxx
735     write(lunout,*)' dzoomy = ', dzoomyy
736     write(lunout,*)' tauxx = ', tauxx
737     write(lunout,*)' tauyy = ', tauyy
738     write(lunout,*)' offline = ', offline
[4608]739     write(lunout,*)' offline_time = ', offline_time
[2142]740     write(lunout,*)' type_trac = ', type_trac
741     write(lunout,*)' ok_dynzon = ', ok_dynzon
742     write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
743     write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
[4146]744     write(lunout,*)' ok_dyn_xios = ', ok_dyn_xios
[4996]745     write(lunout,*)' adv_qsat_liq = ', adv_qsat_liq
[2142]746  else
747     !Config  Key  = clon
748     !Config  Desc = centre du zoom, longitude
749     !Config  Def  = 0
750     !Config  Help = longitude en degres du centre
751     !Config         du zoom
752     clon = 0.
753     CALL getin('clon',clon)
[1632]754
[2142]755     !Config  Key  = clat
756     !Config  Desc = centre du zoom, latitude
757     !Config  Def  = 0
758     !Config  Help = latitude en degres du centre du zoom
759     !Config         
760     clat = 0.
761     CALL getin('clat',clat)
[1632]762
[2142]763     !Config  Key  = grossismx
764     !Config  Desc = zoom en longitude
765     !Config  Def  = 1.0
766     !Config  Help = facteur de grossissement du zoom,
767     !Config         selon la longitude
768     grossismx = 1.0
769     CALL getin('grossismx',grossismx)
[1632]770
[2142]771     !Config  Key  = grossismy
772     !Config  Desc = zoom en latitude
773     !Config  Def  = 1.0
774     !Config  Help = facteur de grossissement du zoom,
775     !Config         selon la latitude
776     grossismy = 1.0
777     CALL getin('grossismy',grossismy)
[1632]778
[2142]779     IF( grossismx.LT.1. )  THEN
[4100]780        write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismx < 1 . *** '
[4469]781        CALL abort_gcm("conf_gcm","stopped",1)
[2142]782     ELSE
783        alphax = 1. - 1./ grossismx
784     ENDIF
[1632]785
[2142]786     IF( grossismy.LT.1. )  THEN
[2141]787        write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
[4469]788        CALL abort_gcm("conf_gcm","stopped",1)
[2142]789     ELSE
790        alphay = 1. - 1./ grossismy
791     ENDIF
[1632]792
[4100]793     write(lunout,*) 'conf_gcm: alphax alphay ',alphax,alphay
[1632]794
[2142]795     !    alphax et alphay sont les anciennes formulat. des grossissements
[1632]796
[2142]797     !Config  Key  = fxyhypb
798     !Config  Desc = Fonction  hyperbolique
799     !Config  Def  = y
800     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
801     !Config         sinon  sinusoidale
802     fxyhypb = .TRUE.
803     CALL getin('fxyhypb',fxyhypb)
[1632]804
[2142]805     !Config  Key  = dzoomx
806     !Config  Desc = extension en longitude
807     !Config  Def  = 0
808     !Config  Help = extension en longitude  de la zone du zoom 
809     !Config         ( fraction de la zone totale)
[2218]810     dzoomx = 0.2
[2142]811     CALL getin('dzoomx',dzoomx)
[2218]812     call assert(dzoomx < 1, "conf_gcm: dzoomx must be < 1")
[1632]813
[2142]814     !Config  Key  = dzoomy
815     !Config  Desc = extension en latitude
816     !Config  Def  = 0
817     !Config  Help = extension en latitude de la zone  du zoom 
818     !Config         ( fraction de la zone totale)
[2218]819     dzoomy = 0.2
[2142]820     CALL getin('dzoomy',dzoomy)
[2218]821     call assert(dzoomy < 1, "conf_gcm: dzoomy must be < 1")
[1632]822
[2142]823     !Config  Key  = taux
824     !Config  Desc = raideur du zoom en  X
825     !Config  Def  = 3
826     !Config  Help = raideur du zoom en  X
827     taux = 3.0
828     CALL getin('taux',taux)
[1632]829
[2142]830     !Config  Key  = tauy
831     !Config  Desc = raideur du zoom en  Y
832     !Config  Def  = 3
833     !Config  Help = raideur du zoom en  Y
834     tauy = 3.0
835     CALL getin('tauy',tauy)
[1632]836
[2142]837     !Config  Key  = ysinus
838     !Config  IF   = !fxyhypb
839     !Config  Desc = Fonction en Sinus
840     !Config  Def  = y
841     !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
842     !Config         sinon y = latit.
843     ysinus = .TRUE.
844     CALL getin('ysinus',ysinus)
[1673]845
[2142]846     !Config  Key  = offline
847     !Config  Desc = Nouvelle eau liquide
848     !Config  Def  = n
849     !Config  Help = Permet de mettre en route la
850     !Config         nouvelle parametrisation de l'eau liquide !
851     offline = .FALSE.
852     CALL getin('offline',offline)
853     IF (offline .AND. adjust) THEN
854        WRITE(lunout,*)  &
855             'WARNING : option offline does not work with adjust=y :'
856        WRITE(lunout,*) 'the files defstoke.nc, fluxstoke.nc ',  &
857             'and fluxstokev.nc will not be created'
858        WRITE(lunout,*)  &
859             'only the file phystoke.nc will still be created '
[4100]860     ENDIF
[1632]861
[2142]862     !Config  Key  = type_trac
863     !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
864     !Config  Def  = lmdz
865     !Config  Help =
866     !Config         'lmdz' = pas de couplage, pur LMDZ
867     !Config         'inca' = model de chime INCA
868     !Config         'repr' = model de chime REPROBUS
869     type_trac = 'lmdz'
870     CALL getin('type_trac',type_trac)
[1632]871
[2142]872     !Config  Key  = ok_dynzon
873     !Config  Desc = sortie des transports zonaux dans la dynamique
874     !Config  Def  = n
875     !Config  Help = Permet de mettre en route le calcul des transports
876     !Config         
877     ok_dynzon = .FALSE.
878     CALL getin('ok_dynzon',ok_dynzon)
[1657]879
[2142]880     !Config  Key  = ok_dyn_ins
881     !Config  Desc = sorties instantanees dans la dynamique
882     !Config  Def  = n
883     !Config  Help =
884     !Config         
885     ok_dyn_ins = .FALSE.
886     CALL getin('ok_dyn_ins',ok_dyn_ins)
887
888     !Config  Key  = ok_dyn_ave
889     !Config  Desc = sorties moyennes dans la dynamique
890     !Config  Def  = n
891     !Config  Help =
892     !Config         
893     ok_dyn_ave = .FALSE.
894     CALL getin('ok_dyn_ave',ok_dyn_ave)
895
[4146]896     !Config  Key  = ok_dyn_xios
897     !Config  Desc = sorties moyennes dans la dynamique
898     !Config  Def  = n
899     !Config  Help =
900     !Config         
901     ok_dyn_xios = .FALSE.
902     CALL getin('ok_dyn_xios',ok_dyn_xios)
903
[2142]904     !Config  Key  = use_filtre_fft
[2444]905     !Config  Desc = flag to activate FFTs for the filter
[2142]906     !Config  Def  = false
[2444]907     !Config  Help = enables to use FFts to do the longitudinal polar
908     !Config         filtering around the poles.
[2142]909     use_filtre_fft=.FALSE.
910     CALL getin('use_filtre_fft',use_filtre_fft)
911     IF (use_filtre_fft .AND. grossismx /= 1.0) THEN
[1632]912        write(lunout,*)'WARNING !!! '
[2444]913        write(lunout,*)"A zoom in longitude is not compatible", &
914             " with the FFT filter ", &
915             "---> FFT filter deactivated"
[2142]916        use_filtre_fft=.FALSE.
917     ENDIF
[2444]918     use_filtre_fft_loc=use_filtre_fft
[1632]919
[2142]920     !Config  Key  = use_mpi_alloc
921     !Config  Desc = Utilise un buffer MPI en m�moire globale
922     !Config  Def  = false
923     !Config  Help = permet d'activer l'utilisation d'un buffer MPI
924     !Config         en m�moire globale a l'aide de la fonction MPI_ALLOC.
925     !Config         Cela peut am�liorer la bande passante des transferts MPI
926     !Config         d'un facteur 2 
927     use_mpi_alloc=.FALSE.
928     CALL getin('use_mpi_alloc',use_mpi_alloc)
[1632]929
[2142]930     !Config key = ok_strato
931     !Config  Desc = activation de la version strato
932     !Config  Def  = .FALSE.
[5267]933     !Config  Help = active la version stratosph�rique de LMDZ de F. Lott
[1632]934
[2142]935     ok_strato=.FALSE.
936     CALL getin('ok_strato',ok_strato)
[1699]937
[2142]938     vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
939     CALL getin('vert_prof_dissip', vert_prof_dissip)
940     call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1, &
941          "bad value for vert_prof_dissip")
[1632]942
[2142]943     !Config  Key  = ok_gradsfile
944     !Config  Desc = activation des sorties grads du guidage
945     !Config  Def  = n
946     !Config  Help = active les sorties grads du guidage
[1632]947
[2142]948     ok_gradsfile = .FALSE.
949     CALL getin('ok_gradsfile',ok_gradsfile)
[1658]950
[2142]951     !Config  Key  = ok_limit
952     !Config  Desc = creation des fichiers limit dans create_etat0_limit
953     !Config  Def  = y
954     !Config  Help = production du fichier limit.nc requise
[1658]955
[2142]956     ok_limit = .TRUE.
957     CALL getin('ok_limit',ok_limit)
[1658]958
[2142]959     !Config  Key  = ok_etat0
960     !Config  Desc = creation des fichiers etat0 dans create_etat0_limit
961     !Config  Def  = y
962     !Config  Help = production des fichiers start.nc, startphy.nc requise
[1658]963
[2142]964     ok_etat0 = .TRUE.
965     CALL getin('ok_etat0',ok_etat0)
966
[2665]967     !Config  Key  = read_orop
968     !Config  Desc = lecture du fichier de params orographiques sous maille
969     !Config  Def  = f
970     !Config  Help = lecture fichier plutot que grid_noro
971
972     read_orop = .FALSE.
973     CALL getin('read_orop',read_orop)
974
[2142]975     write(lunout,*)' #########################################'
[4100]976     write(lunout,*)' Configuration des parametres de cel0_limit: '
[2142]977     write(lunout,*)' planet_type = ', planet_type
978     write(lunout,*)' calend = ', calend
979     write(lunout,*)' dayref = ', dayref
980     write(lunout,*)' anneeref = ', anneeref
981     write(lunout,*)' nday = ', nday
982     write(lunout,*)' day_step = ', day_step
983     write(lunout,*)' iperiod = ', iperiod
984     write(lunout,*)' iconser = ', iconser
985     write(lunout,*)' iecri = ', iecri
986     write(lunout,*)' periodav = ', periodav
987     write(lunout,*)' output_grads_dyn = ', output_grads_dyn
988     write(lunout,*)' dissip_period = ', dissip_period
989     write(lunout,*)' lstardis = ', lstardis
990     write(lunout,*)' nitergdiv = ', nitergdiv
991     write(lunout,*)' nitergrot = ', nitergrot
992     write(lunout,*)' niterh = ', niterh
993     write(lunout,*)' tetagdiv = ', tetagdiv
994     write(lunout,*)' tetagrot = ', tetagrot
995     write(lunout,*)' tetatemp = ', tetatemp
996     write(lunout,*)' coefdis = ', coefdis
997     write(lunout,*)' purmats = ', purmats
998     write(lunout,*)' read_start = ', read_start
999     write(lunout,*)' iflag_phys = ', iflag_phys
1000     write(lunout,*)' iphysiq = ', iphysiq
1001     write(lunout,*)' clon = ', clon
1002     write(lunout,*)' clat = ', clat
1003     write(lunout,*)' grossismx = ', grossismx
1004     write(lunout,*)' grossismy = ', grossismy
1005     write(lunout,*)' fxyhypb = ', fxyhypb
1006     write(lunout,*)' dzoomx = ', dzoomx
1007     write(lunout,*)' dzoomy = ', dzoomy
1008     write(lunout,*)' taux = ', taux
1009     write(lunout,*)' tauy = ', tauy
1010     write(lunout,*)' offline = ', offline
1011     write(lunout,*)' type_trac = ', type_trac
1012     write(lunout,*)' ok_dynzon = ', ok_dynzon
1013     write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
1014     write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
[4146]1015     write(lunout,*)' ok_dyn_xios = ', ok_dyn_xios
[2142]1016     write(lunout,*)' use_filtre_fft = ', use_filtre_fft
1017     write(lunout,*)' use_mpi_alloc = ', use_mpi_alloc
1018     write(lunout,*)' ok_strato = ', ok_strato
1019     write(lunout,*)' ok_gradsfile = ', ok_gradsfile
1020     write(lunout,*)' ok_limit = ', ok_limit
1021     write(lunout,*)' ok_etat0 = ', ok_etat0
[4100]1022     write(lunout,*)' ok_guide = ', ok_guide
[2665]1023     write(lunout,*)' read_orop = ', read_orop
[4100]1024  ENDIF test_etatinit
[2142]1025
1026END SUBROUTINE conf_gcm
Note: See TracBrowser for help on using the repository browser.