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

Last change on this file since 3020 was 2859, checked in by emillour, 2 years ago

PEM:
Follow-up of r2854: remove added stuff in conf_gcm and make a conf_pem instead in order to preserve a clean seperation between dynamics and PEM.
EM

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