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

Last change on this file since 5005 was 4996, checked in by evignon, 2 months ago

ajout d'un flag pour le calcul de qsat dans la condtion de "francis"
pour l'advection de l'humidite (q<qsat_aval). En activant ce flag,
on calcule qsat /liquide quelque soit la temperature et on peut donc
ainsi autoriser l'advection de sursaturations / glace à T<0oC.

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