source: trunk/LMDZ.COMMON/libf/dyn3dpar/conf_gcm.F90 @ 3707

Last change on this file since 3707 was 3615, checked in by emillour, 4 months ago

Venus PCM: Corrections to enable 1+1=2

  • store correctly the time_of_day in restart.nc to enable proper restart
  • enforce recomputation of CP in the physics at all time steps (otherwise when without thermosphere the value was only computed at first step and kept unchanged afterwards).

EM

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