source: trunk/LMDZ.COMMON/libf/dyn3d/conf_gcm.F90 @ 1572

Last change on this file since 1572 was 1572, checked in by emillour, 8 years ago

All GCMs:
Further adaptations to keep up with changes in LMDZ5 concerning
physics/dynamics separation (up to rev r2500 of LMDZ5)

  • arch:
  • remove ifort debug option '-check all', replace it with '-check bounds,format,output_conversion,pointers,uninit' (i.e. get it to stop complaining about copying into temporary arrays)
  • dyn3d_common:
  • comconst_mod.F90 : add ngroup
  • dyn3d:
  • gcm.F90 : minor bug fix (arguments to a call_abort())
  • leapfrog.F90 : recompute geopotential for bilan_dyn outputs
  • conf_gcm.F90 : read "ngroup" from run.def
  • groupe.F , groupeun.F : ngroup no longer a local parameter
  • dyn3d_par:
  • conf_gcm.F90 : read "ngroup" from run.def
  • groupe_p.F , groupeun_p.F : ngroup no longer a local parameter
  • misc:
  • regr1_step_av_m.F90 : removed (not used)
  • phy_common:
  • mod_phys_lmdz_mpi_transfert.F90 , mod_phys_lmdz_mpi_data.F90 : change is_north_pole and is_south_pole to is_north_pole_dyn and is_south_pole_dyn
  • mod_phys_lmdz_omp_data.F90 : introduce is_nort_pole_phy and is_south_pole_phy
  • dynphy_lonlat:
  • mod_interface_dyn_phys.F90 : use is_north_pole_dyn and is_south_pole_dyn
  • calfis_p.F : use is_north_pole_dyn and is_south_pole_dyn
  • phyvenus:
  • physiq_mod , write_hist*.h : use is_north_pole_phy and is_south_pole_phy to correctly compute mesh area at poles to send to hist*nc files.
  • phytitan:
  • physiq_mod , write_hist*.h : use is_north_pole_phy and is_south_pole_phy to correctly compute mesh area at poles to send to hist*nc files.

EM

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