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

Last change on this file since 2126 was 2126, checked in by emillour, 6 years ago

Common dynamics:
Some work to enforce total tracer mass conservation in the dynamics.
Still to be further studied and validated.
For now these changes are triggered by setting a "force_conserv_tracer"
flag to ".true." in run.def (default is ".false." to not change anything
with respect to previous versions).
When force_conserv_tracer=.true. then:

  1. Rescale tracer mass in caladvtrac after tracer advection computations
  2. Recompute q ratios once atmospheric mass has been updated in integrd

These steps technically ensure total tracer mass conservation but it
might be the tracer advection scheme and/or time-stepping updating
sequence of fields that should be rethought or fixed.
EM

File size: 31.7 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                         ecritstart,force_conserv_tracer
20  USE infotrac, ONLY : type_trac
21  use assert_m, only: assert
22  use sponge_mod, only: callsponge,mode_sponge,nsponge,tetasponge
23  USE comconst_mod, ONLY: dissip_factz,dissip_deltaz,dissip_zref,               &
24                dissip_fac_mid,dissip_fac_up,dissip_hdelta,dissip_pupstart,     &
25                mode_top_bound,tau_top_bound,iflag_top_bound,ngroup
26  USE logic_mod, ONLY: tidal,purmats,ok_guide,read_start,iflag_phys,            &
27                iflag_trac,ok_strato,ok_gradsfile,ok_limit,ok_etat0,            &
28                moyzon_mu,moyzon_ch,ok_strato,fxyhypb,ysinus,read_orop
29  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,             &
30                alphax,alphay,taux,tauy
31  USE temps_mod, ONLY: calend
32
33  IMPLICIT NONE
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!
43  LOGICAL,INTENT(IN) :: etatinit
44  INTEGER,INTENT(IN) :: tapedef
45
46!   Declarations :
47!   --------------
48  include "dimensions.h"
49  include "paramet.h"
50  include "comdissnew.h"
51  include "iniprint.h"
52
53!   local:
54!   ------
55
56  REAL clonn,clatt,grossismxx,grossismyy
57  REAL dzoomxx,dzoomyy, tauxx,tauyy
58  LOGICAL  fxyhypbb, ysinuss
59  LOGICAL use_filtre_fft
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!   ----------------
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)
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
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)
106  prt_level = 0
107  CALL getin('prt_level',prt_level)
108
109!-----------------------------------------------------------------------
110!  Parametres de controle du run:
111!-----------------------------------------------------------------------
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
116  planet_type="earth"
117  CALL getin('planet_type',planet_type)
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         
124  calend = 'earth_360d'
125  CALL getin('calend', calend)
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
132  dayref=1
133  CALL getin('dayref', dayref)
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
140  anneeref = 1998
141  CALL getin('anneeref',anneeref)
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
150  raz_date = 0
151  CALL getin('raz_date', raz_date)
152
153!Config  Key  = resetvarc
154!Config  Desc = Reinit des variables de controle
155!Config  Def  = n
156!Config  Help = Reinit des variables de controle
157  resetvarc = .false.
158  CALL getin('resetvarc',resetvarc)
159
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 !
165  nday = 10
166  CALL getin('nday',nday)
167
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)
172     
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
178  starttime = 0
179  CALL getin('starttime',starttime)
180     
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)
185     
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
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
197  less1day = .false.
198  CALL getin('less1day',less1day)
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
204  fractday = 0.01
205  CALL getin('fractday',fractday)
206
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 )
212  day_step = 240
213  CALL getin('day_step',day_step)
214
215!Config  Key  = nsplit_phys
216!Config  Desc = nombre de subdivisions par pas physique
217!Config  Def  = 1
218!Config  Help = nombre de subdivisions par pas physique
219  nsplit_phys = 1
220  CALL getin('nsplit_phys',nsplit_phys)
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)
226  iperiod = 5
227  CALL getin('iperiod',iperiod)
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)
233  iapp_tracvl = iperiod
234  CALL getin('iapp_tracvl',iapp_tracvl)
235
236! Enforce tracer conservation in integrd & caladvtrac ?
237  force_conserv_tracer = .false.
238  CALL getin('force_conserv_tracer',force_conserv_tracer)
239
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)
245  iconser = 240 
246  CALL getin('iconser', iconser)
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)
252  iecri = 1
253  CALL getin('iecri',iecri)
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)
260  periodav = 1.
261  CALL getin('periodav',periodav)
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
267  output_grads_dyn=.false.
268  CALL getin('output_grads_dyn',output_grads_dyn)
269
270!Config  Key  = dissip_period
271!Config  Desc = periode de la dissipation
272!Config  Def  = 0
273!Config  Help = periode de la dissipation
274!Config  dissip_period=0 => la valeur sera calcule dans inidissip       
275!Config  dissip_period>0 => on prend cette valeur
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)
280
281!cc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
282!cc
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 !
290  lstardis = .TRUE.
291  CALL getin('lstardis',lstardis)
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
299  nitergdiv = 1
300  CALL getin('nitergdiv',nitergdiv)
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
307  nitergrot = 2
308  CALL getin('nitergrot',nitergrot)
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
316  niterh = 2
317  CALL getin('niterh',niterh)
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)
325  tetagdiv = 7200.
326  CALL getin('tetagdiv',tetagdiv)
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)
333  tetagrot = 7200.
334  CALL getin('tetagrot',tetagrot)
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)   
341  tetatemp  = 7200.
342  CALL getin('tetatemp',tetatemp )
343
344! For Earth model only:
345! Parametres controlant la variation sur la verticale des constantes de
346! dissipation.
347! Pour le moment actifs uniquement dans la version a 39 niveaux
348! avec ok_strato=y
349
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 )
356
357! For other planets:
358! Parametres controlant la variation sur la verticale des constantes de
359! dissipation.
360! Actifs uniquement avec ok_strato=y
361
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 )
372
373! top_bound sponge: only active if iflag_top_bound!=0
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
377  iflag_top_bound=0
378  CALL getin('iflag_top_bound',iflag_top_bound)
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
385  mode_top_bound=3
386  CALL getin('mode_top_bound',mode_top_bound)
387
388! top_bound sponge : inverse of charactericstic relaxation time scale for sponge
389  tau_top_bound=1.e-5
390  CALL getin('tau_top_bound',tau_top_bound)
391
392! the other possible sponge layer (sponge_mod)
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
404       
405! nsponge: number of atmospheric layers over which the sponge extends
406  nsponge=3 ! default value
407  call getin("nsponge",nsponge)
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)"
413  mode_sponge=2 ! default value
414  call getin("mode_sponge",mode_sponge)
415
416! tetasponge: characteristic time scale (seconds) at topmost layer
417!            (time scale then doubles with decreasing layer index)."
418  tetasponge=50000.0
419  call getin("tetasponge",tetasponge)
420
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
426! FOR TITAN: tidal forces
427  if (planet_type=="titan") then
428    tidal=.TRUE.
429    CALL getin('tidal',tidal)
430  else
431    tidal=.false.
432  endif
433
434!Config  Key  = coefdis
435!Config  Desc = coefficient pour gamdissip
436!Config  Def  = 0
437!Config  Help = coefficient pour gamdissip 
438  coefdis = 0.
439  CALL getin('coefdis',coefdis)
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
446  purmats = .FALSE.
447  CALL getin('purmats',purmats)
448
449!Config  Key  = ok_guide
450!Config  Desc = Guidage
451!Config  Def  = n
452!Config  Help = Guidage
453  ok_guide = .FALSE.
454  CALL getin('ok_guide',ok_guide)
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
461  read_start= .true.
462  CALL getin('read_start',read_start)
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.
469  iflag_phys = 1
470  CALL getin('iflag_phys',iflag_phys)
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.
476  iphysiq = 5
477  CALL getin('iphysiq', iphysiq)
478
479!Config  Key  = iflag_trac
480!Config  Desc = traceurs presents ou non
481!Config  Def  = 1
482!Config  Help = Permet de faire tourner le modele sans traceurs
483!Config         
484  iflag_trac = 1
485  CALL getin('iflag_trac',iflag_trac)
486
487!Config  Key  = ip_ebil_dyn
488!Config  Desc = PRINT level for energy conserv. diag.
489!Config  Def  = 0
490!Config  Help = PRINT level for energy conservation diag. ;
491!               les options suivantes existent :
492!Config         0 pas de print
493!Config         1 pas de print
494!Config         2 print,
495  ip_ebil_dyn = 0
496  CALL getin('ip_ebil_dyn',ip_ebil_dyn)
497
498!Config  Key  = offline
499!Config  Desc = Nouvelle eau liquide
500!Config  Def  = n
501!Config  Help = Permet de mettre en route la
502!Config         nouvelle parametrisation de l'eau liquide !
503  offline = .FALSE.
504  CALL getin('offline',offline)
505
506!Config  Key  = type_trac
507!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
508!Config  Def  = lmdz
509!Config  Help =
510!Config         'lmdz' = pas de couplage, pur LMDZ
511!Config         'inca' = model de chime INCA
512!Config         'repr' = model de chime REPROBUS
513  type_trac = 'lmdz'
514  CALL getin('type_trac',type_trac)
515
516!Config  Key  = config_inca
517!Config  Desc = Choix de configuration de INCA
518!Config  Def  = none
519!Config  Help = Choix de configuration de INCA :
520!Config         'none' = sans INCA
521!Config         'chem' = INCA avec calcul de chemie
522!Config         'aero' = INCA avec calcul des aerosols
523  config_inca = 'none'
524  CALL getin('config_inca',config_inca)
525
526!Config  Key  = ok_dynzon
527!Config  Desc = calcul et sortie des transports
528!Config  Def  = n
529!Config  Help = Permet de mettre en route le calcul des transports
530!Config         
531  ok_dynzon = .FALSE.
532  CALL getin('ok_dynzon',ok_dynzon)
533
534!Config  Key  = ok_dyn_ins
535!Config  Desc = sorties instantanees dans la dynamique
536!Config  Def  = n
537!Config  Help =
538!Config         
539  ok_dyn_ins = .FALSE.
540  CALL getin('ok_dyn_ins',ok_dyn_ins)
541
542!Config  Key  = ok_dyn_ave
543!Config  Desc = sorties moyennes dans la dynamique
544!Config  Def  = n
545!Config  Help =
546!Config         
547  ok_dyn_ave = .FALSE.
548  CALL getin('ok_dyn_ave',ok_dyn_ave)
549
550!Config  Key  = use_filtre_fft
551!Config  Desc = flag d'activation des FFT pour le filtre
552!Config  Def  = false
553!Config  Help = permet d'activer l'utilisation des FFT pour effectuer
554!Config         le filtrage aux poles.
555! Le filtre fft n'est pas implemente dans dyn3d
556  use_filtre_fft=.FALSE.
557  CALL getin('use_filtre_fft',use_filtre_fft)
558
559  IF (use_filtre_fft) THEN
560    write(lunout,*)'STOP !!!'
561    write(lunout,*)'use_filtre_fft not implemented in dyn3d'
562    STOP 1
563  ENDIF
564     
565!Config key = ok_strato
566!Config  Desc = activation de la version strato
567!Config  Def  = .FALSE.
568!Config  Help = active la version stratosphérique de LMDZ de F. Lott
569
570  ok_strato=.TRUE.
571  CALL getin('ok_strato',ok_strato)
572
573! NB: vert_prof_dissip is Earth-specific; should not impact other models
574  if (planet_type=="earth") then
575    vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
576    CALL getin('vert_prof_dissip', vert_prof_dissip)
577    call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1, &
578         "bad value for vert_prof_dissip")
579  else
580    vert_prof_dissip=0 ! default for planets !
581    if (planet_type=="mars") then
582      vert_prof_dissip=1 ! use fac_mid & fac_up & startalt & delta
583    endif
584  endif
585
586!Config  Key  = ok_gradsfile
587!Config  Desc = activation des sorties grads du guidage
588!Config  Def  = n
589!Config  Help = active les sorties grads du guidage
590
591  ok_gradsfile = .FALSE.
592  CALL getin('ok_gradsfile',ok_gradsfile)
593
594!Config  Key  = ok_limit
595!Config  Desc = creation des fichiers limit dans create_etat0_limit
596!Config  Def  = y
597!Config  Help = production du fichier limit.nc requise
598
599  ok_limit = .TRUE.
600  CALL getin('ok_limit',ok_limit)
601
602!Config  Key  = ok_etat0
603!Config  Desc = creation des fichiers etat0 dans create_etat0_limit
604!Config  Def  = y
605!Config  Help = production des fichiers start.nc, startphy.nc requise
606
607  ok_etat0 = .TRUE.
608  CALL getin('ok_etat0',ok_etat0)
609
610!Config  Key  = read_orop
611!Config  Desc = lecture du fichier de params orographiques sous maille
612!Config  Def  = f
613!Config  Help = lecture fichier plutot que grid_noro
614
615  read_orop = .FALSE.
616  CALL getin('read_orop',read_orop)
617
618!----------------------------------------
619! Parameters for zonal averages in the case of Titan
620  moyzon_mu = .false.
621  moyzon_ch = .false.
622  if (planet_type=="titan") then
623    CALL getin('moyzon_mu', moyzon_mu)
624    CALL getin('moyzon_ch', moyzon_ch)
625  endif
626!----------------------------------------
627
628!----------------------------------------
629!cc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
630!     .........   (  modif  le 17/04/96 )   .........
631!
632! ZOOM PARAMETERS ... the ones read in start.nc prevail anyway ! (SL, 2012)
633!
634!----------------------------------------
635  test_etatinit: IF (.not. etatinit) then
636     !Config  Key  = clon
637     !Config  Desc = centre du zoom, longitude
638     !Config  Def  = 0
639     !Config  Help = longitude en degres du centre
640     !Config         du zoom
641     clonn = 0.
642     CALL getin('clon',clonn)
643
644     !Config  Key  = clat
645     !Config  Desc = centre du zoom, latitude
646     !Config  Def  = 0
647     !Config  Help = latitude en degres du centre du zoom
648     !Config         
649     clatt = 0.
650     CALL getin('clat',clatt)
651
652     IF( ABS(clat - clatt).GE. 0.001 )  THEN
653        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def', &
654             ' est differente de celle lue sur le fichier  start '
655        STOP
656     ENDIF
657
658     !Config  Key  = grossismx
659     !Config  Desc = zoom en longitude
660     !Config  Def  = 1.0
661     !Config  Help = facteur de grossissement du zoom,
662     !Config         selon la longitude
663     grossismxx = 1.0
664     CALL getin('grossismx',grossismxx)
665
666     IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
667        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ', &
668             'run.def est differente de celle lue sur le fichier  start '
669        STOP
670     ENDIF
671
672     !Config  Key  = grossismy
673     !Config  Desc = zoom en latitude
674     !Config  Def  = 1.0
675     !Config  Help = facteur de grossissement du zoom,
676     !Config         selon la latitude
677     grossismyy = 1.0
678     CALL getin('grossismy',grossismyy)
679
680     IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
681        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ', &
682             'run.def est differente de celle lue sur le fichier  start '
683        STOP
684     ENDIF
685
686     IF( grossismx.LT.1. )  THEN
687        write(lunout,*) &
688             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
689        STOP
690     ELSE
691        alphax = 1. - 1./ grossismx
692     ENDIF
693
694     IF( grossismy.LT.1. )  THEN
695        write(lunout,*) &
696             'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
697        STOP
698     ELSE
699        alphay = 1. - 1./ grossismy
700     ENDIF
701
702     write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
703
704     !    alphax et alphay sont les anciennes formulat. des grossissements
705
706     !Config  Key  = fxyhypb
707     !Config  Desc = Fonction  hyperbolique
708     !Config  Def  = y
709     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
710     !Config         sinon  sinusoidale
711     fxyhypbb = .TRUE.
712     CALL getin('fxyhypb',fxyhypbb)
713
714     IF( .NOT.fxyhypb )  THEN
715        IF( fxyhypbb )     THEN
716           write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
717           write(lunout,*)' *** fxyhypb lu sur le fichier start est ', &
718                'F alors  qu il est  T  sur  run.def  ***'
719           STOP
720        ENDIF
721     ELSE
722        IF( .NOT.fxyhypbb )   THEN
723           write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
724           write(lunout,*)' ***  fxyhypb lu sur le fichier start est ', &
725                'T alors  qu il est  F  sur  run.def  ****  '
726           STOP
727        ENDIF
728     ENDIF
729
730     !Config  Key  = dzoomx
731     !Config  Desc = extension en longitude
732     !Config  Def  = 0
733     !Config  Help = extension en longitude  de la zone du zoom 
734     !Config         ( fraction de la zone totale)
735     dzoomxx = 0.0
736     CALL getin('dzoomx',dzoomxx)
737
738     IF( fxyhypb )  THEN
739        IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
740           write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ', &
741                'run.def est differente de celle lue sur le fichier  start '
742           STOP
743        ENDIF
744     ENDIF
745
746     !Config  Key  = dzoomy
747     !Config  Desc = extension en latitude
748     !Config  Def  = 0
749     !Config  Help = extension en latitude de la zone  du zoom 
750     !Config         ( fraction de la zone totale)
751     dzoomyy = 0.0
752     CALL getin('dzoomy',dzoomyy)
753
754     IF( fxyhypb )  THEN
755        IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
756           write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ', &
757                'run.def est differente de celle lue sur le fichier  start '
758           STOP
759        ENDIF
760     ENDIF
761
762     !Config  Key  = taux
763     !Config  Desc = raideur du zoom en  X
764     !Config  Def  = 3
765     !Config  Help = raideur du zoom en  X
766     tauxx = 3.0
767     CALL getin('taux',tauxx)
768
769     IF( fxyhypb )  THEN
770        IF( ABS(taux - tauxx).GE. 0.001 )  THEN
771           write(lunout,*)'conf_gcm: La valeur de taux passee par ', &
772                'run.def est differente de celle lue sur le fichier  start '
773           STOP
774        ENDIF
775     ENDIF
776
777     !Config  Key  = tauyy
778     !Config  Desc = raideur du zoom en  Y
779     !Config  Def  = 3
780     !Config  Help = raideur du zoom en  Y
781     tauyy = 3.0
782     CALL getin('tauy',tauyy)
783
784     IF( fxyhypb )  THEN
785        IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
786           write(lunout,*)'conf_gcm: La valeur de tauy passee par ', &
787                'run.def est differente de celle lue sur le fichier  start '
788           STOP
789        ENDIF
790     ENDIF
791
792     !c
793     IF( .NOT.fxyhypb  )  THEN
794
795        !Config  Key  = ysinus
796        !Config  IF   = !fxyhypb
797        !Config  Desc = Fonction en Sinus
798        !Config  Def  = y
799        !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
800        !Config         sinon y = latit.
801        ysinuss = .TRUE.
802        CALL getin('ysinus',ysinuss)
803
804        IF( .NOT.ysinus )  THEN
805           IF( ysinuss )     THEN
806              write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
807              write(lunout,*)' *** ysinus lu sur le fichier start est F', &
808                   ' alors  qu il est  T  sur  run.def  ***'
809              STOP
810           ENDIF
811        ELSE
812           IF( .NOT.ysinuss )   THEN
813              write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
814              write(lunout,*)' *** ysinus lu sur le fichier start est T', &
815                   ' alors  qu il est  F  sur  run.def  ****  '
816              STOP
817           ENDIF
818        ENDIF
819     ENDIF ! of IF( .NOT.fxyhypb  )
820  else
821     !Config  Key  = clon
822     !Config  Desc = centre du zoom, longitude
823     !Config  Def  = 0
824     !Config  Help = longitude en degres du centre
825     !Config         du zoom
826     clon = 0.
827     CALL getin('clon',clon)
828
829     !Config  Key  = clat
830     !Config  Desc = centre du zoom, latitude
831     !Config  Def  = 0
832     !Config  Help = latitude en degres du centre du zoom
833     !Config         
834     clat = 0.
835     CALL getin('clat',clat)
836
837     !Config  Key  = grossismx
838     !Config  Desc = zoom en longitude
839     !Config  Def  = 1.0
840     !Config  Help = facteur de grossissement du zoom,
841     !Config         selon la longitude
842     grossismx = 1.0
843     CALL getin('grossismx',grossismx)
844
845     !Config  Key  = grossismy
846     !Config  Desc = zoom en latitude
847     !Config  Def  = 1.0
848     !Config  Help = facteur de grossissement du zoom,
849     !Config         selon la latitude
850     grossismy = 1.0
851     CALL getin('grossismy',grossismy)
852
853     IF( grossismx.LT.1. )  THEN
854        write(lunout,*) &
855             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
856        STOP
857     ELSE
858        alphax = 1. - 1./ grossismx
859     ENDIF
860
861     IF( grossismy.LT.1. )  THEN
862        write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
863        STOP
864     ELSE
865        alphay = 1. - 1./ grossismy
866     ENDIF
867
868     write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
869
870     !    alphax et alphay sont les anciennes formulat. des grossissements
871
872     !Config  Key  = fxyhypb
873     !Config  Desc = Fonction  hyperbolique
874     !Config  Def  = y
875     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
876     !Config         sinon  sinusoidale
877     fxyhypb = .TRUE.
878     CALL getin('fxyhypb',fxyhypb)
879
880     !Config  Key  = dzoomx
881     !Config  Desc = extension en longitude
882     !Config  Def  = 0
883     !Config  Help = extension en longitude  de la zone du zoom 
884     !Config         ( fraction de la zone totale)
885     dzoomx = 0.2
886     CALL getin('dzoomx',dzoomx)
887     call assert(dzoomx < 1, "conf_gcm: dzoomx must be < 1")
888
889     !Config  Key  = dzoomy
890     !Config  Desc = extension en latitude
891     !Config  Def  = 0
892     !Config  Help = extension en latitude de la zone  du zoom 
893     !Config         ( fraction de la zone totale)
894     dzoomy = 0.2
895     CALL getin('dzoomy',dzoomy)
896     call assert(dzoomy < 1, "conf_gcm: dzoomy must be < 1")
897
898     !Config  Key  = taux
899     !Config  Desc = raideur du zoom en  X
900     !Config  Def  = 3
901     !Config  Help = raideur du zoom en  X
902     taux = 3.0
903     CALL getin('taux',taux)
904
905     !Config  Key  = tauy
906     !Config  Desc = raideur du zoom en  Y
907     !Config  Def  = 3
908     !Config  Help = raideur du zoom en  Y
909     tauy = 3.0
910     CALL getin('tauy',tauy)
911
912     !Config  Key  = ysinus
913     !Config  IF   = !fxyhypb
914     !Config  Desc = Fonction en Sinus
915     !Config  Def  = y
916     !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
917     !Config         sinon y = latit.
918     ysinus = .TRUE.
919     CALL getin('ysinus',ysinus)
920
921  end IF test_etatinit
922!----------------------------------------
923
924
925 write(lunout,*)' #########################################'
926 write(lunout,*)' Configuration des parametres lus via run.def '
927 write(lunout,*)' planet_type = ', planet_type
928 write(lunout,*)' calend = ', calend
929 write(lunout,*)' dayref = ', dayref
930 write(lunout,*)' anneeref = ', anneeref
931 write(lunout,*)' nday = ', nday
932 if (ndynstep.ne.-9999) write(lunout,*)' ndynstep = ', ndynstep
933 if (less1day) write(lunout,*)' fractday = ', fractday
934 write(lunout,*)' day_step = ', day_step
935 write(lunout,*)' iperiod = ', iperiod
936 write(lunout,*)' nsplit_phys = ', nsplit_phys
937 write(lunout,*)' iconser = ', iconser
938 write(lunout,*)' iecri = ', iecri
939 write(lunout,*)' periodav = ', periodav
940 write(lunout,*)' output_grads_dyn = ', output_grads_dyn
941 write(lunout,*)' dissip_period = ', dissip_period
942 write(lunout,*)' lstardis = ', lstardis
943 write(lunout,*)' nitergdiv = ', nitergdiv
944 write(lunout,*)' nitergrot = ', nitergrot
945 write(lunout,*)' niterh = ', niterh
946 write(lunout,*)' tetagdiv = ', tetagdiv
947 write(lunout,*)' tetagrot = ', tetagrot
948 write(lunout,*)' tetatemp = ', tetatemp
949 write(lunout,*)' coefdis = ', coefdis
950 write(lunout,*)' purmats = ', purmats
951 write(lunout,*)' read_start = ', read_start
952 write(lunout,*)' iflag_phys = ', iflag_phys
953 write(lunout,*)' iphysiq = ', iphysiq
954 write(lunout,*)' iflag_trac = ', iflag_trac
955 write(lunout,*)' iapp_tracvl = ', iapp_tracvl
956 write(lunout,*)' force_conserv_tracer = ', force_conserv_tracer
957 write(lunout,*)' clon = ', clon
958 write(lunout,*)' clat = ', clat
959 write(lunout,*)' grossismx = ', grossismx
960 write(lunout,*)' grossismy = ', grossismy
961 write(lunout,*)' fxyhypb = ', fxyhypb
962 write(lunout,*)' dzoomx = ', dzoomx
963 write(lunout,*)' dzoomy = ', dzoomy
964 write(lunout,*)' taux = ', taux
965 write(lunout,*)' tauy = ', tauy
966 write(lunout,*)' offline = ', offline
967 write(lunout,*)' type_trac = ', type_trac
968 write(lunout,*)' config_inca = ', config_inca
969 write(lunout,*)' ok_dynzon = ', ok_dynzon
970 write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
971 write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
972 write(lunout,*)' ok_strato = ', ok_strato
973 write(lunout,*)' ok_gradsfile = ', ok_gradsfile
974 write(lunout,*)' ok_limit = ', ok_limit
975 write(lunout,*)' ok_etat0 = ', ok_etat0
976 write(lunout,*)' read_orop = ', read_orop
977 if (planet_type=="titan") then
978   write(lunout,*)' moyzon_mu = ', moyzon_mu
979   write(lunout,*)' moyzon_ch = ', moyzon_ch
980 endif
981
982END SUBROUTINE conf_gcm
Note: See TracBrowser for help on using the repository browser.