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

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