source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/lmdz_conf_gcm.f90 @ 5411

Last change on this file since 5411 was 5186, checked in by abarral, 3 months ago

Encapsulate files in modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 36.1 KB
Line 
1MODULE lmdz_conf_gcm
2  IMPLICIT NONE; PRIVATE
3  PUBLIC conf_gcm
4
5CONTAINS
6
7  SUBROUTINE conf_gcm(tapedef, etatinit)
8
9    USE control_mod
10    USE IOIPSL
11    USE misc_mod
12    USE lmdz_filtre_fft, ONLY: use_filtre_fft
13    USE lmdz_filtre_fft_loc, ONLY: use_filtre_fft_loc => use_filtre_fft
14    USE mod_hallo, ONLY: use_mpi_alloc
15    USE lmdz_infotrac, ONLY: type_trac
16    USE lmdz_assert, ONLY: assert
17    USE comconst_mod, ONLY: dissip_deltaz, dissip_factz, dissip_zref, &
18            iflag_top_bound, mode_top_bound, tau_top_bound, &
19            ngroup, maxlatfilter
20    USE logic_mod, ONLY: fxyhypb, iflag_phys, ok_etat0, ok_gradsfile, &
21            ok_guide, ok_limit, ok_strato, purmats, read_start, &
22            ysinus, read_orop, adv_qsat_liq
23    USE serre_mod, ONLY: clon, clat, grossismx, grossismy, dzoomx, dzoomy, &
24            alphax, alphay, taux, tauy
25    USE temps_mod, ONLY: calend, year_len, offline_time
26    USE lmdz_iniprint, ONLY: lunout, prt_level
27    USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
28            tetagrot, tetatemp, coefdis, vert_prof_dissip
29
30    USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
31    USE lmdz_paramet
32    IMPLICIT NONE
33    !-----------------------------------------------------------------------
34    !     Auteurs :   L. Fairhead , P. Le Van  .
35
36    !     Arguments :
37
38    !     tapedef   :
39    !     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
40    !     -metres  du zoom  avec  celles lues sur le fichier start .
41
42    LOGICAL, INTENT(IN) :: etatinit
43    INTEGER, INTENT(IN) :: tapedef
44
45    !   Declarations :
46    !   --------------
47
48
49
50    !   local:
51    !   ------
52
53    CHARACTER ch1*72, ch2*72, ch3*72, ch4*12
54    REAL clonn, clatt, grossismxx, grossismyy
55    REAL dzoomxx, dzoomyy, tauxx, tauyy
56    LOGICAL  fxyhypbb, ysinuss
57    INTEGER i
58    CHARACTER(len = *), PARAMETER :: modname = "conf_gcm"
59    CHARACTER(len = 80) :: abort_message
60#ifdef CPP_OMP
61  INTEGER, EXTERNAL :: OMP_GET_NUM_THREADS
62#endif
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_0000', ACTION = 'write', &
101              STATUS = 'unknown', FORM = 'formatted')
102    ENDIF
103
104    adjust = .FALSE.
105    CALL getin('adjust', adjust)
106
107#ifdef CPP_OMP
108  ! adjust=y not implemented in case of OpenMP threads...
109  !$OMP PARALLEL
110  IF ((OMP_GET_NUM_THREADS()>1).AND.adjust) THEN
111     WRITE(lunout,*)'conf_gcm: Error, adjust should be set to n' &
112          ,' when running with OpenMP threads'
113     abort_message = 'Wrong value for adjust'
114     CALL abort_gcm(modname,abort_message,1)
115  ENDIF
116  !$OMP END PARALLEL         
117#endif
118
119    itaumax = 0
120    CALL getin('itaumax', itaumax);
121    IF (itaumax<=0) itaumax = HUGE(itaumax)
122
123    !Config  Key  = prt_level
124    !Config  Desc = niveau d'impressions de débogage
125    !Config  Def  = 0
126    !Config  Help = Niveau d'impression pour le débogage
127    !Config         (0 = minimum d'impression)
128    prt_level = 0
129    CALL getin('prt_level', prt_level)
130
131    !-----------------------------------------------------------------------
132    !  Parametres de controle du run:
133    !-----------------------------------------------------------------------
134    !Config  Key  = planet_type
135    !Config  Desc = planet type ("earth", "mars", "venus", ...)
136    !Config  Def  = earth
137    !Config  Help = this flag sets the type of atymosphere that is considered
138    planet_type = "earth"
139    CALL getin('planet_type', planet_type)
140
141    !Config  Key  = calend
142    !Config  Desc = type de calendrier utilise
143    !Config  Def  = earth_360d
144    !Config  Help = valeur possible: earth_360d, earth_365d, earth_366d
145    !Config
146    calend = 'earth_360d'
147    ! initialize year_len for aquaplanets and 1D
148    CALL getin('calend', calend)
149    IF (calend == 'earth_360d') THEN
150      year_len = 360
151    ELSE IF (calend == 'earth_365d') THEN
152      year_len = 365
153    ELSE IF (calend == 'earth_366d') THEN
154      year_len = 366
155    ELSE
156      year_len = 1
157    ENDIF
158
159    !Config  Key  = dayref
160    !Config  Desc = Jour de l'etat initial
161    !Config  Def  = 1
162    !Config  Help = Jour de l'etat initial ( = 350  si 20 Decembre ,
163    !Config         par expl. ,comme ici ) ... A completer
164    dayref = 1
165    CALL getin('dayref', dayref)
166
167    !Config  Key  = anneeref
168    !Config  Desc = Annee de l'etat initial
169    !Config  Def  = 1998
170    !Config  Help = Annee de l'etat  initial
171    !Config         (   avec  4  chiffres   ) ... A completer
172    anneeref = 1998
173    CALL getin('anneeref', anneeref)
174
175    !Config  Key  = raz_date
176    !Config  Desc = Remise a zero de la date initiale
177    !Config  Def  = 0 (pas de remise a zero)
178    !Config  Help = Remise a zero de la date initiale
179    !Config         0 pas de remise a zero, on garde la date du fichier restart
180    !Config         1 prise en compte de la date de gcm.def avec remise a zero
181    !Config         des compteurs de pas de temps
182    raz_date = 0
183    CALL getin('raz_date', raz_date)
184
185    !Config  Key  = resetvarc
186    !Config  Desc = Reinit des variables de controle
187    !Config  Def  = n
188    !Config  Help = Reinit des variables de controle
189    resetvarc = .FALSE.
190    CALL getin('resetvarc', resetvarc)
191
192    !Config  Key  = nday
193    !Config  Desc = Nombre de jours d'integration
194    !Config  Def  = 10
195    !Config  Help = Nombre de jours d'integration
196    !Config         ... On pourait aussi permettre des mois ou des annees !
197    nday = 10
198    CALL getin('nday', nday)
199
200    !Config  Key  = starttime
201    !Config  Desc = Heure de depart de la simulation
202    !Config  Def  = 0
203    !Config  Help = Heure de depart de la simulation
204    !Config         en jour
205    starttime = 0
206    CALL getin('starttime', starttime)
207
208    !Config  Key  = day_step
209    !Config  Desc = nombre de pas par jour
210    !Config  Def  = 240
211    !Config  Help = nombre de pas par jour (multiple de iperiod) (
212    !Config          ici pour  dt = 1 min )
213    day_step = 240
214    CALL getin('day_step', day_step)
215
216    !Config  Key  = nsplit_phys
217    nsplit_phys = 1
218    CALL getin('nsplit_phys', nsplit_phys)
219
220    !Config  Key  = iperiod
221    !Config  Desc = periode pour le pas Matsuno
222    !Config  Def  = 5
223    !Config  Help = periode pour le pas Matsuno (en pas de temps)
224    iperiod = 5
225    CALL getin('iperiod', iperiod)
226
227    !Config  Key  = iapp_tracvl
228    !Config  Desc = frequence du groupement des flux
229    !Config  Def  = iperiod
230    !Config  Help = frequence du groupement des flux (en pas de temps)
231    iapp_tracvl = iperiod
232    CALL getin('iapp_tracvl', iapp_tracvl)
233
234    !Config  Key  = iconser
235    !Config  Desc = periode de sortie des variables de controle
236    !Config  Def  = 240
237    !Config  Help = periode de sortie des variables de controle
238    !Config         (En pas de temps)
239    iconser = 240
240    CALL getin('iconser', iconser)
241
242    !Config  Key  = iecri
243    !Config  Desc = periode d'ecriture du fichier histoire
244    !Config  Def  = 1
245    !Config  Help = periode d'ecriture du fichier histoire (en jour)
246    iecri = 1
247    CALL getin('iecri', iecri)
248
249    !Config  Key  = periodav
250    !Config  Desc = periode de stockage fichier histmoy
251    !Config  Def  = 1
252    !Config  Help = periode de stockage fichier histmoy (en jour)
253    periodav = 1.
254    CALL getin('periodav', periodav)
255
256    !Config  Key  = output_grads_dyn
257    !Config  Desc = output dynamics diagnostics in 'dyn.dat' file
258    !Config  Def  = n
259    !Config  Help = output dynamics diagnostics in Grads-readable 'dyn.dat' file
260    output_grads_dyn = .FALSE.
261    CALL getin('output_grads_dyn', output_grads_dyn)
262
263    !Config  Key  = dissip_period
264    !Config  Desc = periode de la dissipation
265    !Config  Def  = 0
266    !Config  Help = periode de la dissipation
267    !Config  dissip_period=0 => la valeur sera calcule dans inidissip
268    !Config  dissip_period>0 => on prend cette valeur
269    dissip_period = 0
270    CALL getin('dissip_period', dissip_period)
271
272    !cc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
273    !cc
274
275    !Config  Key  = lstardis
276    !Config  Desc = choix de l'operateur de dissipation
277    !Config  Def  = y
278    !Config  Help = choix de l'operateur de dissipation
279    !Config         'y' si on veut star et 'n' si on veut non-start !
280    !Config         Moi y en a pas comprendre !
281    lstardis = .TRUE.
282    CALL getin('lstardis', lstardis)
283
284    !Config  Key  = nitergdiv
285    !Config  Desc = Nombre d'iteration de gradiv
286    !Config  Def  = 1
287    !Config  Help = nombre d'iterations de l'operateur de dissipation
288    !Config         gradiv
289    nitergdiv = 1
290    CALL getin('nitergdiv', nitergdiv)
291
292    !Config  Key  = nitergrot
293    !Config  Desc = nombre d'iterations de nxgradrot
294    !Config  Def  = 2
295    !Config  Help = nombre d'iterations de l'operateur de dissipation
296    !Config         nxgradrot
297    nitergrot = 2
298    CALL getin('nitergrot', nitergrot)
299
300    !Config  Key  = niterh
301    !Config  Desc = nombre d'iterations de divgrad
302    !Config  Def  = 2
303    !Config  Help = nombre d'iterations de l'operateur de dissipation
304    !Config         divgrad
305    niterh = 2
306    CALL getin('niterh', niterh)
307
308    !Config  Key  = tetagdiv
309    !Config  Desc = temps de dissipation pour div
310    !Config  Def  = 7200
311    !Config  Help = temps de dissipation des plus petites longeur
312    !Config         d'ondes pour u,v (gradiv)
313    tetagdiv = 7200.
314    CALL getin('tetagdiv', tetagdiv)
315
316    !Config  Key  = tetagrot
317    !Config  Desc = temps de dissipation pour grad
318    !Config  Def  = 7200
319    !Config  Help = temps de dissipation des plus petites longeur
320    !Config         d'ondes pour u,v (nxgradrot)
321    tetagrot = 7200.
322    CALL getin('tetagrot', tetagrot)
323
324    !Config  Key  = tetatemp
325    !Config  Desc = temps de dissipation pour h
326    !Config  Def  = 7200
327    !Config  Help =  temps de dissipation des plus petites longeur
328    !Config         d'ondes pour h (divgrad)
329    tetatemp = 7200.
330    CALL getin('tetatemp', tetatemp)
331
332    ! Parametres controlant la variation sur la verticale des constantes de
333    ! dissipation.
334    ! Pour le moment actifs uniquement dans la version a 39 niveaux
335    ! avec ok_strato=y
336
337    dissip_factz = 4.
338    dissip_deltaz = 10.
339    dissip_zref = 30.
340    CALL getin('dissip_factz', dissip_factz)
341    CALL getin('dissip_deltaz', dissip_deltaz)
342    CALL getin('dissip_zref', dissip_zref)
343
344
345    !maxlatfilter
346    maxlatfilter = -1.0
347    CALL getin('maxlatfilter', maxlatfilter)
348    IF (maxlatfilter > 90) &
349            CALL abort_gcm("conf_gcm", 'maxlatfilter should be <=90', 1)
350
351
352    ! ngroup
353    ngroup = 3
354    CALL getin('ngroup', ngroup)
355    IF (mod(iim, 2**ngroup) /= 0) &
356            CALL abort_gcm("conf_gcm", 'iim must be multiple of 2**ngroup', 1)
357    IF (2**ngroup > jjm + 1) &
358            CALL abort_gcm("conf_gcm", '2**ngroup must be <= jjm + 1', 1)
359
360    ! mode_top_bound : fields towards which sponge relaxation will be done:
361    ! top_bound sponge: only active if ok_strato=.TRUE. and iflag_top_bound!=0
362    !                   iflag_top_bound=0 for no sponge
363    !                   iflag_top_bound=1 for sponge over 4 topmost layers
364    !                   iflag_top_bound=2 for sponge from top to ~1% of top layer pressure
365    iflag_top_bound = 1
366    CALL getin('iflag_top_bound', iflag_top_bound)
367    IF (iflag_top_bound < 0 .OR. iflag_top_bound > 2) &
368            CALL abort_gcm("conf_gcm", 'iflag_top_bound must be 0, 1 or 2', 1)
369
370    ! mode_top_bound : fields towards which sponge relaxation will be done:
371    !                  mode_top_bound=0: no relaxation
372    !                  mode_top_bound=1: u and v relax towards 0
373    !                  mode_top_bound=2: u and v relax towards their zonal mean
374    !                  mode_top_bound=3: u,v and pot. temp. relax towards their zonal mean
375    mode_top_bound = 3
376    CALL getin('mode_top_bound', mode_top_bound)
377
378    ! top_bound sponge : inverse of charactericstic relaxation time scale for sponge
379    tau_top_bound = 1.e-5
380    CALL getin('tau_top_bound', tau_top_bound)
381
382    !Config  Key  = coefdis
383    !Config  Desc = coefficient pour gamdissip
384    !Config  Def  = 0
385    !Config  Help = coefficient pour gamdissip
386    coefdis = 0.
387    CALL getin('coefdis', coefdis)
388
389    !Config  Key  = purmats
390    !Config  Desc = Schema d'integration
391    !Config  Def  = n
392    !Config  Help = Choix du schema d'integration temporel.
393    !Config         y = pure Matsuno sinon c'est du Matsuno-leapfrog
394    purmats = .FALSE.
395    CALL getin('purmats', purmats)
396
397    !Config  Key  = ok_guide
398    !Config  Desc = Guidage
399    !Config  Def  = n
400    !Config  Help = Guidage
401    ok_guide = .FALSE.
402    CALL getin('ok_guide', ok_guide)
403
404    IF (ok_guide .AND. adjust) CALL abort_gcm("conf_gcm", &
405            "adjust does not work with ok_guide", 1)
406
407    !Config  Key  =  read_start
408    !Config  Desc = Initialize model using a 'start.nc' file
409    !Config  Def  = y
410    !Config  Help = y: intialize dynamical fields using a 'start.nc' file
411    !               n: fields are initialized by 'iniacademic' routine
412    read_start = .TRUE.
413    CALL getin('read_start', read_start)
414
415    !Config  Key  = iflag_phys
416    !Config  Desc = Avec ls physique
417    !Config  Def  = 1
418    !Config  Help = Permet de faire tourner le modele sans
419    !Config         physique.
420    iflag_phys = 1
421    CALL getin('iflag_phys', iflag_phys)
422
423    !Config  Key  =  iphysiq
424    !Config  Desc = Periode de la physique
425    !Config  Def  = 5
426    !Config  Help = Periode de la physique en pas de temps de la dynamique.
427    iphysiq = 5
428    CALL getin('iphysiq', iphysiq)
429
430    !Config  Key  = ip_ebil_dyn
431    !Config  Desc = PRINT level for energy conserv. diag.
432    !Config  Def  = 0
433    !Config  Help = PRINT level for energy conservation diag. ;
434    !               les options suivantes existent :
435    !Config         0 pas de print
436    !Config         1 pas de print
437    !Config         2 print,
438    ip_ebil_dyn = 0
439    CALL getin('ip_ebil_dyn', ip_ebil_dyn)
440
441    !cc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
442    !     .........   (  modif  le 17/04/96 )   .........
443
444    test_etatinit: IF (.NOT. etatinit) THEN
445      !Config  Key  = clon
446      !Config  Desc = centre du zoom, longitude
447      !Config  Def  = 0
448      !Config  Help = longitude en degres du centre
449      !Config         du zoom
450      clonn = 0.
451      CALL getin('clon', clonn)
452
453      !Config  Key  = clat
454      !Config  Desc = centre du zoom, latitude
455      !Config  Def  = 0
456      !Config  Help = latitude en degres du centre du zoom
457      !Config
458      clatt = 0.
459      CALL getin('clat', clatt)
460
461      IF(ABS(clat - clatt)>= 0.001)  THEN
462        WRITE(lunout, *)'conf_gcm: La valeur de clat passee par run.def', &
463                ' est differente de celle lue sur le fichier  start '
464        CALL abort_gcm("conf_gcm", "stopped", 1)
465      ENDIF
466
467      !Config  Key  = grossismx
468      !Config  Desc = zoom en longitude
469      !Config  Def  = 1.0
470      !Config  Help = facteur de grossissement du zoom,
471      !Config         selon la longitude
472      grossismxx = 1.0
473      CALL getin('grossismx', grossismxx)
474
475      IF(ABS(grossismx - grossismxx)>= 0.001)  THEN
476        WRITE(lunout, *)'conf_gcm: La valeur de grossismx passee par ', &
477                'run.def est differente de celle lue sur le fichier  start '
478        CALL abort_gcm("conf_gcm", "stopped", 1)
479      ENDIF
480
481      !Config  Key  = grossismy
482      !Config  Desc = zoom en latitude
483      !Config  Def  = 1.0
484      !Config  Help = facteur de grossissement du zoom,
485      !Config         selon la latitude
486      grossismyy = 1.0
487      CALL getin('grossismy', grossismyy)
488
489      IF(ABS(grossismy - grossismyy)>= 0.001)  THEN
490        WRITE(lunout, *)'conf_gcm: La valeur de grossismy passee par ', &
491                'run.def est differente de celle lue sur le fichier  start '
492        CALL abort_gcm("conf_gcm", "stopped", 1)
493      ENDIF
494
495      IF(grossismx<1.)  THEN
496        WRITE(lunout, *) &
497                'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
498        CALL abort_gcm("conf_gcm", "stopped", 1)
499      ELSE
500        alphax = 1. - 1. / grossismx
501      ENDIF
502
503      IF(grossismy<1.)  THEN
504        WRITE(lunout, *) &
505                'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
506        CALL abort_gcm("conf_gcm", "stopped", 1)
507      ELSE
508        alphay = 1. - 1. / grossismy
509      ENDIF
510
511      WRITE(lunout, *)'conf_gcm: alphax alphay', alphax, alphay
512
513      !    alphax et alphay sont les anciennes formulat. des grossissements
514
515      !Config  Key  = fxyhypb
516      !Config  Desc = Fonction  hyperbolique
517      !Config  Def  = y
518      !Config  Help = Fonction  f(y)  hyperbolique  si = .TRUE.
519      !Config         sinon  sinusoidale
520      fxyhypbb = .TRUE.
521      CALL getin('fxyhypb', fxyhypbb)
522
523      IF(.NOT.fxyhypb)  THEN
524        IF(fxyhypbb)     THEN
525          WRITE(lunout, *)' ********  PBS DANS  CONF_GCM  ******** '
526          WRITE(lunout, *)' *** fxyhypb lu sur le fichier start est ', &
527                  'F alors  qu il est  T  sur  run.def  ***'
528          CALL abort_gcm("conf_gcm", "stopped", 1)
529        ENDIF
530      ELSE
531        IF(.NOT.fxyhypbb)   THEN
532          WRITE(lunout, *)' ********  PBS DANS  CONF_GCM  ******** '
533          WRITE(lunout, *)' ***  fxyhypb lu sur le fichier start est ', &
534                  'T alors  qu il est  F  sur  run.def  ****  '
535          CALL abort_gcm("conf_gcm", "stopped", 1)
536        ENDIF
537      ENDIF
538
539      !Config  Key  = dzoomx
540      !Config  Desc = extension en longitude
541      !Config  Def  = 0
542      !Config  Help = extension en longitude  de la zone du zoom
543      !Config         ( fraction de la zone totale)
544      dzoomxx = 0.0
545      CALL getin('dzoomx', dzoomxx)
546
547      IF(fxyhypb)  THEN
548        IF(ABS(dzoomx - dzoomxx)>= 0.001)  THEN
549          WRITE(lunout, *)'conf_gcm: La valeur de dzoomx passee par ', &
550                  'run.def est differente de celle lue sur le fichier  start '
551          CALL abort_gcm("conf_gcm", "stopped", 1)
552        ENDIF
553      ENDIF
554
555      !Config  Key  = dzoomy
556      !Config  Desc = extension en latitude
557      !Config  Def  = 0
558      !Config  Help = extension en latitude de la zone  du zoom
559      !Config         ( fraction de la zone totale)
560      dzoomyy = 0.0
561      CALL getin('dzoomy', dzoomyy)
562
563      IF(fxyhypb)  THEN
564        IF(ABS(dzoomy - dzoomyy)>= 0.001)  THEN
565          WRITE(lunout, *)'conf_gcm: La valeur de dzoomy passee par ', &
566                  'run.def est differente de celle lue sur le fichier  start '
567          CALL abort_gcm("conf_gcm", "stopped", 1)
568        ENDIF
569      ENDIF
570
571      !Config  Key  = taux
572      !Config  Desc = raideur du zoom en  X
573      !Config  Def  = 3
574      !Config  Help = raideur du zoom en  X
575      tauxx = 3.0
576      CALL getin('taux', tauxx)
577
578      IF(fxyhypb)  THEN
579        IF(ABS(taux - tauxx)>= 0.001)  THEN
580          WRITE(lunout, *)'conf_gcm: La valeur de taux passee par ', &
581                  'run.def est differente de celle lue sur le fichier  start '
582          CALL abort_gcm("conf_gcm", "stopped", 1)
583        ENDIF
584      ENDIF
585
586      !Config  Key  = tauyy
587      !Config  Desc = raideur du zoom en  Y
588      !Config  Def  = 3
589      !Config  Help = raideur du zoom en  Y
590      tauyy = 3.0
591      CALL getin('tauy', tauyy)
592
593      IF(fxyhypb)  THEN
594        IF(ABS(tauy - tauyy)>= 0.001)  THEN
595          WRITE(lunout, *)'conf_gcm: La valeur de tauy passee par ', &
596                  'run.def est differente de celle lue sur le fichier  start '
597          CALL abort_gcm("conf_gcm", "stopped", 1)
598        ENDIF
599      ENDIF
600
601      !c
602      IF(.NOT.fxyhypb)  THEN
603
604        !Config  Key  = ysinus
605        !Config  IF   = !fxyhypb
606        !Config  Desc = Fonction en Sinus
607        !Config  Def  = y
608        !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .TRUE.
609        !Config         sinon y = latit.
610        ysinuss = .TRUE.
611        CALL getin('ysinus', ysinuss)
612
613        IF(.NOT.ysinus)  THEN
614          IF(ysinuss)     THEN
615            WRITE(lunout, *)' ********  PBS DANS  CONF_GCM  ******** '
616            WRITE(lunout, *)' *** ysinus lu sur le fichier start est F', &
617                    ' alors  qu il est  T  sur  run.def  ***'
618            CALL abort_gcm("conf_gcm", "stopped", 1)
619          ENDIF
620        ELSE
621          IF(.NOT.ysinuss)   THEN
622            WRITE(lunout, *)' ********  PBS DANS  CONF_GCM  ******** '
623            WRITE(lunout, *)' *** ysinus lu sur le fichier start est T', &
624                    ' alors  qu il est  F  sur  run.def  ****  '
625            CALL abort_gcm("conf_gcm", "stopped", 1)
626          ENDIF
627        ENDIF
628      ENDIF ! of IF( .NOT.fxyhypb  )
629
630      !Config  Key  = offline
631      !Config  Desc = ecriture des flux de masse
632      !Config  Def  = n
633      !Config  Help = Permet de sortir les flux de masse sur la grille plev
634      offline = .FALSE.
635      CALL getin('offline', offline)
636
637      !Config Key  = offline_time
638      !Config Desc =  Choix des frequences de stockage pour le offline
639      !Config Def  = 8
640      !Config Help = offline_time=12     ! stockage toutes les 2h=1jour/12
641      !Config Help = offline_time=8      ! stockage toutes les 3h=1jour/8
642      offline_time = 8
643      CALL getin('offline_time', offline_time)
644
645      IF (offline .AND. adjust) THEN
646        WRITE(lunout, *)  &
647                'WARNING : option offline does not work with adjust=y :'
648        WRITE(lunout, *) 'the files defstoke.nc, fluxstoke.nc ', &
649                'and fluxstokev.nc will not be created'
650        WRITE(lunout, *)  &
651                'only the file phystoke.nc will still be created '
652      ENDIF
653
654      !Config  Key  = type_trac
655      !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
656      !Config  Def  = lmdz
657      !Config  Help =
658      !Config         'lmdz' = pas de couplage, pur LMDZ
659      !Config         'inca' = model de chime INCA
660      !Config         'repr' = model de chime REPROBUS
661      type_trac = 'lmdz'
662      CALL getin('type_trac', type_trac)
663
664
665      !Config  Key  = adv_qsat_liq
666      !Config  Desc = option for qsat calculation in the dynamics
667      !Config  Def  = n
668      !Config  Help = controls which phase is considered for qsat calculation
669      !Config
670      adv_qsat_liq = .FALSE.
671      CALL getin('adv_qsat_liq', adv_qsat_liq)
672
673      !Config  Key  = ok_dynzon
674      !Config  Desc = calcul et sortie des transports
675      !Config  Def  = n
676      !Config  Help = Permet de mettre en route le calcul des transports
677      !Config
678      ok_dynzon = .FALSE.
679      CALL getin('ok_dynzon', ok_dynzon)
680
681      !Config  Key  = ok_dyn_ins
682      !Config  Desc = sorties instantanees dans la dynamique
683      !Config  Def  = n
684      !Config  Help =
685      !Config
686      ok_dyn_ins = .FALSE.
687      CALL getin('ok_dyn_ins', ok_dyn_ins)
688
689      !Config  Key  = ok_dyn_ave
690      !Config  Desc = sorties moyennes dans la dynamique
691      !Config  Def  = n
692      !Config  Help =
693      !Config
694      ok_dyn_ave = .FALSE.
695      CALL getin('ok_dyn_ave', ok_dyn_ave)
696
697      !Config  Key  = ok_dyn_xios
698      !Config  Desc = sorties moyennes dans la dynamique
699      !Config  Def  = n
700      !Config  Help =
701      !Config
702      ok_dyn_xios = .FALSE.
703      CALL getin('ok_dyn_xios', ok_dyn_xios)
704
705      WRITE(lunout, *)' #########################################'
706      WRITE(lunout, *)' Configuration des parametres du gcm: '
707      WRITE(lunout, *)' planet_type = ', planet_type
708      WRITE(lunout, *)' calend = ', calend
709      WRITE(lunout, *)' dayref = ', dayref
710      WRITE(lunout, *)' anneeref = ', anneeref
711      WRITE(lunout, *)' nday = ', nday
712      WRITE(lunout, *)' day_step = ', day_step
713      WRITE(lunout, *)' iperiod = ', iperiod
714      WRITE(lunout, *)' nsplit_phys = ', nsplit_phys
715      WRITE(lunout, *)' iconser = ', iconser
716      WRITE(lunout, *)' iecri = ', iecri
717      WRITE(lunout, *)' periodav = ', periodav
718      WRITE(lunout, *)' output_grads_dyn = ', output_grads_dyn
719      WRITE(lunout, *)' dissip_period = ', dissip_period
720      WRITE(lunout, *)' lstardis = ', lstardis
721      WRITE(lunout, *)' nitergdiv = ', nitergdiv
722      WRITE(lunout, *)' nitergrot = ', nitergrot
723      WRITE(lunout, *)' niterh = ', niterh
724      WRITE(lunout, *)' tetagdiv = ', tetagdiv
725      WRITE(lunout, *)' tetagrot = ', tetagrot
726      WRITE(lunout, *)' tetatemp = ', tetatemp
727      WRITE(lunout, *)' coefdis = ', coefdis
728      WRITE(lunout, *)' purmats = ', purmats
729      WRITE(lunout, *)' read_start = ', read_start
730      WRITE(lunout, *)' iflag_phys = ', iflag_phys
731      WRITE(lunout, *)' iphysiq = ', iphysiq
732      WRITE(lunout, *)' clonn = ', clonn
733      WRITE(lunout, *)' clatt = ', clatt
734      WRITE(lunout, *)' grossismx = ', grossismx
735      WRITE(lunout, *)' grossismy = ', grossismy
736      WRITE(lunout, *)' fxyhypbb = ', fxyhypbb
737      WRITE(lunout, *)' dzoomxx = ', dzoomxx
738      WRITE(lunout, *)' dzoomy = ', dzoomyy
739      WRITE(lunout, *)' tauxx = ', tauxx
740      WRITE(lunout, *)' tauyy = ', tauyy
741      WRITE(lunout, *)' offline = ', offline
742      WRITE(lunout, *)' offline_time = ', offline_time
743      WRITE(lunout, *)' type_trac = ', type_trac
744      WRITE(lunout, *)' ok_dynzon = ', ok_dynzon
745      WRITE(lunout, *)' ok_dyn_ins = ', ok_dyn_ins
746      WRITE(lunout, *)' ok_dyn_ave = ', ok_dyn_ave
747      WRITE(lunout, *)' ok_dyn_xios = ', ok_dyn_xios
748      WRITE(lunout, *)' adv_qsat_liq = ', adv_qsat_liq
749    else
750      !Config  Key  = clon
751      !Config  Desc = centre du zoom, longitude
752      !Config  Def  = 0
753      !Config  Help = longitude en degres du centre
754      !Config         du zoom
755      clon = 0.
756      CALL getin('clon', clon)
757
758      !Config  Key  = clat
759      !Config  Desc = centre du zoom, latitude
760      !Config  Def  = 0
761      !Config  Help = latitude en degres du centre du zoom
762      !Config
763      clat = 0.
764      CALL getin('clat', clat)
765
766      !Config  Key  = grossismx
767      !Config  Desc = zoom en longitude
768      !Config  Def  = 1.0
769      !Config  Help = facteur de grossissement du zoom,
770      !Config         selon la longitude
771      grossismx = 1.0
772      CALL getin('grossismx', grossismx)
773
774      !Config  Key  = grossismy
775      !Config  Desc = zoom en latitude
776      !Config  Def  = 1.0
777      !Config  Help = facteur de grossissement du zoom,
778      !Config         selon la latitude
779      grossismy = 1.0
780      CALL getin('grossismy', grossismy)
781
782      IF(grossismx<1.)  THEN
783        WRITE(lunout, *) 'conf_gcm: ***ATTENTION !! grossismx < 1 . *** '
784        CALL abort_gcm("conf_gcm", "stopped", 1)
785      ELSE
786        alphax = 1. - 1. / grossismx
787      ENDIF
788
789      IF(grossismy<1.)  THEN
790        WRITE(lunout, *) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
791        CALL abort_gcm("conf_gcm", "stopped", 1)
792      ELSE
793        alphay = 1. - 1. / grossismy
794      ENDIF
795
796      WRITE(lunout, *) 'conf_gcm: alphax alphay ', alphax, alphay
797
798      !    alphax et alphay sont les anciennes formulat. des grossissements
799
800      !Config  Key  = fxyhypb
801      !Config  Desc = Fonction  hyperbolique
802      !Config  Def  = y
803      !Config  Help = Fonction  f(y)  hyperbolique  si = .TRUE.
804      !Config         sinon  sinusoidale
805      fxyhypb = .TRUE.
806      CALL getin('fxyhypb', fxyhypb)
807
808      !Config  Key  = dzoomx
809      !Config  Desc = extension en longitude
810      !Config  Def  = 0
811      !Config  Help = extension en longitude  de la zone du zoom
812      !Config         ( fraction de la zone totale)
813      dzoomx = 0.2
814      CALL getin('dzoomx', dzoomx)
815      CALL assert(dzoomx < 1, "conf_gcm: dzoomx must be < 1")
816
817      !Config  Key  = dzoomy
818      !Config  Desc = extension en latitude
819      !Config  Def  = 0
820      !Config  Help = extension en latitude de la zone  du zoom
821      !Config         ( fraction de la zone totale)
822      dzoomy = 0.2
823      CALL getin('dzoomy', dzoomy)
824      CALL assert(dzoomy < 1, "conf_gcm: dzoomy must be < 1")
825
826      !Config  Key  = taux
827      !Config  Desc = raideur du zoom en  X
828      !Config  Def  = 3
829      !Config  Help = raideur du zoom en  X
830      taux = 3.0
831      CALL getin('taux', taux)
832
833      !Config  Key  = tauy
834      !Config  Desc = raideur du zoom en  Y
835      !Config  Def  = 3
836      !Config  Help = raideur du zoom en  Y
837      tauy = 3.0
838      CALL getin('tauy', tauy)
839
840      !Config  Key  = ysinus
841      !Config  IF   = !fxyhypb
842      !Config  Desc = Fonction en Sinus
843      !Config  Def  = y
844      !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .TRUE.
845      !Config         sinon y = latit.
846      ysinus = .TRUE.
847      CALL getin('ysinus', ysinus)
848
849      !Config  Key  = offline
850      !Config  Desc = Nouvelle eau liquide
851      !Config  Def  = n
852      !Config  Help = Permet de mettre en route la
853      !Config         nouvelle parametrisation de l'eau liquide !
854      offline = .FALSE.
855      CALL getin('offline', offline)
856      IF (offline .AND. adjust) THEN
857        WRITE(lunout, *)  &
858                'WARNING : option offline does not work with adjust=y :'
859        WRITE(lunout, *) 'the files defstoke.nc, fluxstoke.nc ', &
860                'and fluxstokev.nc will not be created'
861        WRITE(lunout, *)  &
862                'only the file phystoke.nc will still be created '
863      ENDIF
864
865      !Config  Key  = type_trac
866      !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
867      !Config  Def  = lmdz
868      !Config  Help =
869      !Config         'lmdz' = pas de couplage, pur LMDZ
870      !Config         'inca' = model de chime INCA
871      !Config         'repr' = model de chime REPROBUS
872      type_trac = 'lmdz'
873      CALL getin('type_trac', type_trac)
874
875      !Config  Key  = ok_dynzon
876      !Config  Desc = sortie des transports zonaux dans la dynamique
877      !Config  Def  = n
878      !Config  Help = Permet de mettre en route le calcul des transports
879      !Config
880      ok_dynzon = .FALSE.
881      CALL getin('ok_dynzon', ok_dynzon)
882
883      !Config  Key  = ok_dyn_ins
884      !Config  Desc = sorties instantanees dans la dynamique
885      !Config  Def  = n
886      !Config  Help =
887      !Config
888      ok_dyn_ins = .FALSE.
889      CALL getin('ok_dyn_ins', ok_dyn_ins)
890
891      !Config  Key  = ok_dyn_ave
892      !Config  Desc = sorties moyennes dans la dynamique
893      !Config  Def  = n
894      !Config  Help =
895      !Config
896      ok_dyn_ave = .FALSE.
897      CALL getin('ok_dyn_ave', ok_dyn_ave)
898
899      !Config  Key  = ok_dyn_xios
900      !Config  Desc = sorties moyennes dans la dynamique
901      !Config  Def  = n
902      !Config  Help =
903      !Config
904      ok_dyn_xios = .FALSE.
905      CALL getin('ok_dyn_xios', ok_dyn_xios)
906
907      !Config  Key  = use_filtre_fft
908      !Config  Desc = flag to activate FFTs for the filter
909      !Config  Def  = false
910      !Config  Help = enables to use FFts to do the longitudinal polar
911      !Config         filtering around the poles.
912      use_filtre_fft = .FALSE.
913      CALL getin('use_filtre_fft', use_filtre_fft)
914      IF (use_filtre_fft .AND. grossismx /= 1.0) THEN
915        WRITE(lunout, *)'WARNING !!! '
916        WRITE(lunout, *)"A zoom in longitude is not compatible", &
917                " with the FFT filter ", &
918                "---> FFT filter deactivated"
919        use_filtre_fft = .FALSE.
920      ENDIF
921      use_filtre_fft_loc = use_filtre_fft
922
923      !Config  Key  = use_mpi_alloc
924      !Config  Desc = Utilise un buffer MPI en mémoire globale
925      !Config  Def  = false
926      !Config  Help = permet d'activer l'utilisation d'un buffer MPI
927      !Config         en mémoire globale a l'aide de la fonction MPI_ALLOC.
928      !Config         Cela peut améliorer la bande passante des transferts MPI
929      !Config         d'un facteur 2
930      use_mpi_alloc = .FALSE.
931      CALL getin('use_mpi_alloc', use_mpi_alloc)
932
933      !Config key = ok_strato
934      !Config  Desc = activation de la version strato
935      !Config  Def  = .FALSE.
936      !Config  Help = active la version stratosphérique de LMDZ de F. Lott
937
938      ok_strato = .FALSE.
939      CALL getin('ok_strato', ok_strato)
940
941      vert_prof_dissip = merge(1, 0, ok_strato .AND. llm==39)
942      CALL getin('vert_prof_dissip', vert_prof_dissip)
943      CALL assert(vert_prof_dissip == 0 .OR. vert_prof_dissip ==  1, &
944              "bad value for vert_prof_dissip")
945
946      !Config  Key  = ok_gradsfile
947      !Config  Desc = activation des sorties grads du guidage
948      !Config  Def  = n
949      !Config  Help = active les sorties grads du guidage
950
951      ok_gradsfile = .FALSE.
952      CALL getin('ok_gradsfile', ok_gradsfile)
953
954      !Config  Key  = ok_limit
955      !Config  Desc = creation des fichiers limit dans create_etat0_limit
956      !Config  Def  = y
957      !Config  Help = production du fichier limit.nc requise
958
959      ok_limit = .TRUE.
960      CALL getin('ok_limit', ok_limit)
961
962      !Config  Key  = ok_etat0
963      !Config  Desc = creation des fichiers etat0 dans create_etat0_limit
964      !Config  Def  = y
965      !Config  Help = production des fichiers start.nc, startphy.nc requise
966
967      ok_etat0 = .TRUE.
968      CALL getin('ok_etat0', ok_etat0)
969
970      !Config  Key  = read_orop
971      !Config  Desc = lecture du fichier de params orographiques sous maille
972      !Config  Def  = f
973      !Config  Help = lecture fichier plutot que grid_noro
974
975      read_orop = .FALSE.
976      CALL getin('read_orop', read_orop)
977
978      WRITE(lunout, *)' #########################################'
979      WRITE(lunout, *)' Configuration des parametres de cel0_limit: '
980      WRITE(lunout, *)' planet_type = ', planet_type
981      WRITE(lunout, *)' calend = ', calend
982      WRITE(lunout, *)' dayref = ', dayref
983      WRITE(lunout, *)' anneeref = ', anneeref
984      WRITE(lunout, *)' nday = ', nday
985      WRITE(lunout, *)' day_step = ', day_step
986      WRITE(lunout, *)' iperiod = ', iperiod
987      WRITE(lunout, *)' iconser = ', iconser
988      WRITE(lunout, *)' iecri = ', iecri
989      WRITE(lunout, *)' periodav = ', periodav
990      WRITE(lunout, *)' output_grads_dyn = ', output_grads_dyn
991      WRITE(lunout, *)' dissip_period = ', dissip_period
992      WRITE(lunout, *)' lstardis = ', lstardis
993      WRITE(lunout, *)' nitergdiv = ', nitergdiv
994      WRITE(lunout, *)' nitergrot = ', nitergrot
995      WRITE(lunout, *)' niterh = ', niterh
996      WRITE(lunout, *)' tetagdiv = ', tetagdiv
997      WRITE(lunout, *)' tetagrot = ', tetagrot
998      WRITE(lunout, *)' tetatemp = ', tetatemp
999      WRITE(lunout, *)' coefdis = ', coefdis
1000      WRITE(lunout, *)' purmats = ', purmats
1001      WRITE(lunout, *)' read_start = ', read_start
1002      WRITE(lunout, *)' iflag_phys = ', iflag_phys
1003      WRITE(lunout, *)' iphysiq = ', iphysiq
1004      WRITE(lunout, *)' clon = ', clon
1005      WRITE(lunout, *)' clat = ', clat
1006      WRITE(lunout, *)' grossismx = ', grossismx
1007      WRITE(lunout, *)' grossismy = ', grossismy
1008      WRITE(lunout, *)' fxyhypb = ', fxyhypb
1009      WRITE(lunout, *)' dzoomx = ', dzoomx
1010      WRITE(lunout, *)' dzoomy = ', dzoomy
1011      WRITE(lunout, *)' taux = ', taux
1012      WRITE(lunout, *)' tauy = ', tauy
1013      WRITE(lunout, *)' offline = ', offline
1014      WRITE(lunout, *)' type_trac = ', type_trac
1015      WRITE(lunout, *)' ok_dynzon = ', ok_dynzon
1016      WRITE(lunout, *)' ok_dyn_ins = ', ok_dyn_ins
1017      WRITE(lunout, *)' ok_dyn_ave = ', ok_dyn_ave
1018      WRITE(lunout, *)' ok_dyn_xios = ', ok_dyn_xios
1019      WRITE(lunout, *)' use_filtre_fft = ', use_filtre_fft
1020      WRITE(lunout, *)' use_mpi_alloc = ', use_mpi_alloc
1021      WRITE(lunout, *)' ok_strato = ', ok_strato
1022      WRITE(lunout, *)' ok_gradsfile = ', ok_gradsfile
1023      WRITE(lunout, *)' ok_limit = ', ok_limit
1024      WRITE(lunout, *)' ok_etat0 = ', ok_etat0
1025      WRITE(lunout, *)' ok_guide = ', ok_guide
1026      WRITE(lunout, *)' read_orop = ', read_orop
1027    ENDIF test_etatinit
1028
1029  END SUBROUTINE conf_gcm
1030
1031
1032END MODULE lmdz_conf_gcm
Note: See TracBrowser for help on using the repository browser.