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

Last change on this file since 2856 was 2854, checked in by llange, 3 years ago

PEM
Conf_gcm is adapted to read the PEM.def files to simulate orbital parameter evolutions in the PEM
RV & LL

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