source: LMDZ6/branches/Amaury_dev/libf/dyn3d/conf_gcm.f90 @ 5123

Last change on this file since 5123 was 5118, checked in by abarral, 2 months ago

Replace iniprint.h by lmdz_iniprint.f90
(lint) along the way

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