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

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

Dynamical core: Further adaptations to stick with LMDZ5 (up to rev r2750)

  • libf
  • makelmdz[_fcm] : added Earth-specific "dust" and "strataer" cases and

-arch_path option

  • bld.cfg : added dust and strataer cases
  • dyn3d[par]
  • conf_gcm.F90 : added read_orop parameter (Earth-related) for

loading subgrid orography parameters.

  • guide[_p]_mod.F90: added output of nudging coefficients for winds

and temperature

  • temps_mod.F90 : cosmetics/comments
  • logic_mod.F90 : cosmetics/comments
  • dyn3d_common
  • comconst_mod.F90 : cosmetics/comments + added year_day module variable
  • conf_planete.F90 : added year_day from comconst_mod as done in LMDZ5
  • comvert_mod.F90 : cosmetics/comments
  • infotrac.F90 : added "startAer" case to follow up with LMDZ5
  • misc
  • wxios.F90 : follow up on changes in LMDZ5

EM

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