source: LMDZ6/trunk/libf/dyn3d/conf_gcm.F90 @ 4055

Last change on this file since 4055 was 4055, checked in by lguez, 2 years ago

Check that the value of iflag_top_bound is valid

This check is useful because if iflag_top_bound is not between 0 and
2 then the program runs with an undefined value of lambda in procedure
top_bound_loc.

  • 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.8 KB
Line 
1
2! $Id: conf_gcm.F90 4055 2022-01-10 12:59:19Z lguez $
3
4SUBROUTINE conf_gcm( tapedef, etatinit )
5
6  USE control_mod
7#ifdef CPP_IOIPSL
8  use IOIPSL
9#else
10  ! if not using IOIPSL, we still need to use (a local version of) getin
11  use ioipsl_getincom
12#endif
13  USE infotrac, ONLY : type_trac
14  use assert_m, only: assert
15  USE comconst_mod, ONLY: dissip_deltaz, dissip_factz, dissip_zref, &
16                          iflag_top_bound, mode_top_bound, tau_top_bound, &
17                          ngroup
18  USE logic_mod, ONLY: fxyhypb, iflag_phys, ok_etat0, ok_gradsfile, &
19                       ok_guide, ok_limit, ok_strato, purmats, read_start, &
20                       ysinus, read_orop
21  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
22                       alphax,alphay,taux,tauy
23  USE temps_mod, ONLY: calend, year_len
24
25  IMPLICIT NONE
26  !-----------------------------------------------------------------------
27  !     Auteurs :   L. Fairhead , P. Le Van  .
28
29  !     Arguments :
30
31  !     tapedef   :
32  !     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
33  !     -metres  du zoom  avec  celles lues sur le fichier start .
34
35  LOGICAL,INTENT(IN) :: etatinit
36  INTEGER,INTENT(IN) :: tapedef
37
38  !   Declarations :
39  !   --------------
40  include "dimensions.h"
41  include "paramet.h"
42  include "comdissnew.h"
43  include "iniprint.h"
44
45  !   local:
46  !   ------
47
48  REAL clonn,clatt,grossismxx,grossismyy
49  REAL dzoomxx,dzoomyy, tauxx,tauyy
50  LOGICAL  fxyhypbb, ysinuss
51
52  !  -------------------------------------------------------------------
53
54  !       .........     Version  du 29/04/97       ..........
55
56  !   Nouveaux parametres nitergdiv,nitergrot,niterh,tetagdiv,tetagrot,
57  !      tetatemp   ajoutes  pour la dissipation   .
58
59  !   Autre parametre ajoute en fin de liste de tapedef : ** fxyhypb **
60
61  !  Si fxyhypb = .TRUE. , choix de la fonction a derivee tangente hyperb.
62  !    Sinon , choix de fxynew  , a derivee sinusoidale  ..
63
64  !   ......  etatinit = . TRUE. si defrun  est appele dans ETAT0_LMD  ou
65  !         LIMIT_LMD  pour l'initialisation de start.dat (dic) et
66  !                de limit.dat ( dic)                        ...........
67  !           Sinon  etatinit = . FALSE .
68
69  !   Donc etatinit = .F.  si on veut comparer les valeurs de  grossismx ,
70  !    grossismy,clon,clat, fxyhypb  lues sur  le fichier  start  avec
71  !   celles passees  par run.def ,  au debut du gcm, apres l'appel a
72  !    lectba . 
73  !   Ces parmetres definissant entre autres la grille et doivent etre
74  !   pareils et coherents , sinon il y aura  divergence du gcm .
75
76  !-----------------------------------------------------------------------
77  !   initialisations:
78  !   ----------------
79
80  !Config  Key  = lunout
81  !Config  Desc = unite de fichier pour les impressions
82  !Config  Def  = 6
83  !Config  Help = unite de fichier pour les impressions
84  !Config         (defaut sortie standard = 6)
85  lunout=6
86  CALL getin('lunout', lunout)
87  IF (lunout /= 5 .and. lunout /= 6) THEN
88     OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',                      &
89          STATUS='unknown',FORM='formatted')
90  ENDIF
91
92  !Config  Key  = prt_level
93  !Config  Desc = niveau d'impressions de d\'ebogage
94  !Config  Def  = 0
95  !Config  Help = Niveau d'impression pour le d\'ebogage
96  !Config         (0 = minimum d'impression)
97  prt_level = 0
98  CALL getin('prt_level',prt_level)
99
100  !-----------------------------------------------------------------------
101  !  Parametres de controle du run:
102  !-----------------------------------------------------------------------
103  !Config  Key  = planet_type
104  !Config  Desc = planet type ("earth", "mars", "venus", ...)
105  !Config  Def  = earth
106  !Config  Help = this flag sets the type of atymosphere that is considered
107  planet_type="earth"
108  CALL getin('planet_type',planet_type)
109
110  !Config  Key  = calend
111  !Config  Desc = type de calendrier utilise
112  !Config  Def  = earth_360d
113  !Config  Help = valeur possible: earth_360d, earth_365d, earth_366d
114  !Config         
115  calend = 'earth_360d'
116  CALL getin('calend', calend)
117! initialize year_len for aquaplanets and 1D
118      if (calend == 'earth_360d') then
119        year_len=360
120      else if (calend == 'earth_365d') then
121        year_len=365
122      else if (calend == 'earth_366d') then
123        year_len=366
124      else
125        year_len=1
126      endif
127
128  !Config  Key  = dayref
129  !Config  Desc = Jour de l'etat initial
130  !Config  Def  = 1
131  !Config  Help = Jour de l'etat initial ( = 350  si 20 Decembre ,
132  !Config         par expl. ,comme ici ) ... A completer
133  dayref=1
134  CALL getin('dayref', dayref)
135
136  !Config  Key  = anneeref
137  !Config  Desc = Annee de l'etat initial
138  !Config  Def  = 1998
139  !Config  Help = Annee de l'etat  initial
140  !Config         (   avec  4  chiffres   ) ... A completer
141  anneeref = 1998
142  CALL getin('anneeref',anneeref)
143
144  !Config  Key  = raz_date
145  !Config  Desc = Remise a zero de la date initiale
146  !Config  Def  = 0 (pas de remise a zero)
147  !Config  Help = Remise a zero de la date initiale
148  !Config         0 pas de remise a zero, on garde la date du fichier restart
149  !Config         1 prise en compte de la date de gcm.def avec remise a zero
150  !Config         des compteurs de pas de temps
151  raz_date = 0
152  CALL getin('raz_date', raz_date)
153
154  !Config  Key  = resetvarc
155  !Config  Desc = Reinit des variables de controle
156  !Config  Def  = n
157  !Config  Help = Reinit des variables de controle
158  resetvarc = .false.
159  CALL getin('resetvarc',resetvarc)
160
161  !Config  Key  = nday
162  !Config  Desc = Nombre de jours d'integration
163  !Config  Def  = 10
164  !Config  Help = Nombre de jours d'integration
165  !Config         ... On pourait aussi permettre des mois ou des annees !
166  nday = 10
167  CALL getin('nday',nday)
168
169  !Config  Key  = starttime
170  !Config  Desc = Heure de depart de la simulation
171  !Config  Def  = 0
172  !Config  Help = Heure de depart de la simulation
173  !Config         en jour
174  starttime = 0
175  CALL getin('starttime',starttime)
176
177  !Config  Key  = day_step
178  !Config  Desc = nombre de pas par jour
179  !Config  Def  = 240
180  !Config  Help = nombre de pas par jour (multiple de iperiod) (
181  !Config          ici pour  dt = 1 min )
182  day_step = 240
183  CALL getin('day_step',day_step)
184
185  !Config  Key  = nsplit_phys
186  nsplit_phys = 1
187  CALL getin('nsplit_phys',nsplit_phys)
188
189  !Config  Key  = iperiod
190  !Config  Desc = periode pour le pas Matsuno
191  !Config  Def  = 5
192  !Config  Help = periode pour le pas Matsuno (en pas de temps)
193  iperiod = 5
194  CALL getin('iperiod',iperiod)
195
196  !Config  Key  = iapp_tracvl
197  !Config  Desc = frequence du groupement des flux
198  !Config  Def  = iperiod
199  !Config  Help = frequence du groupement des flux (en pas de temps)
200  iapp_tracvl = iperiod
201  CALL getin('iapp_tracvl',iapp_tracvl)
202
203  !Config  Key  = iconser
204  !Config  Desc = periode de sortie des variables de controle
205  !Config  Def  = 240 
206  !Config  Help = periode de sortie des variables de controle
207  !Config         (En pas de temps)
208  iconser = 240 
209  CALL getin('iconser', iconser)
210
211  !Config  Key  = iecri
212  !Config  Desc = periode d'ecriture du fichier histoire
213  !Config  Def  = 1
214  !Config  Help = periode d'ecriture du fichier histoire (en jour)
215  iecri = 1
216  CALL getin('iecri',iecri)
217
218  !Config  Key  = periodav
219  !Config  Desc = periode de stockage fichier histmoy
220  !Config  Def  = 1
221  !Config  Help = periode de stockage fichier histmoy (en jour)
222  periodav = 1.
223  CALL getin('periodav',periodav)
224
225  !Config  Key  = output_grads_dyn
226  !Config  Desc = output dynamics diagnostics in 'dyn.dat' file
227  !Config  Def  = n
228  !Config  Help = output dynamics diagnostics in Grads-readable 'dyn.dat' file
229  output_grads_dyn=.false.
230  CALL getin('output_grads_dyn',output_grads_dyn)
231
232  !Config  Key  = dissip_period
233  !Config  Desc = periode de la dissipation
234  !Config  Def  = 0
235  !Config  Help = periode de la dissipation
236  !Config  dissip_period=0 => la valeur sera calcule dans inidissip       
237  !Config  dissip_period>0 => on prend cette valeur
238  dissip_period = 0
239  CALL getin('dissip_period',dissip_period)
240
241  !cc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
242  !cc
243
244  !Config  Key  = lstardis
245  !Config  Desc = choix de l'operateur de dissipation
246  !Config  Def  = y
247  !Config  Help = choix de l'operateur de dissipation
248  !Config         'y' si on veut star et 'n' si on veut non-start !
249  !Config         Moi y en a pas comprendre !
250  lstardis = .TRUE.
251  CALL getin('lstardis',lstardis)
252
253  !Config  Key  = nitergdiv
254  !Config  Desc = Nombre d'iteration de gradiv
255  !Config  Def  = 1
256  !Config  Help = nombre d'iterations de l'operateur de dissipation
257  !Config         gradiv
258  nitergdiv = 1
259  CALL getin('nitergdiv',nitergdiv)
260
261  !Config  Key  = nitergrot
262  !Config  Desc = nombre d'iterations de nxgradrot
263  !Config  Def  = 2
264  !Config  Help = nombre d'iterations de l'operateur de dissipation 
265  !Config         nxgradrot
266  nitergrot = 2
267  CALL getin('nitergrot',nitergrot)
268
269  !Config  Key  = niterh
270  !Config  Desc = nombre d'iterations de divgrad
271  !Config  Def  = 2
272  !Config  Help = nombre d'iterations de l'operateur de dissipation
273  !Config         divgrad
274  niterh = 2
275  CALL getin('niterh',niterh)
276
277  !Config  Key  = tetagdiv
278  !Config  Desc = temps de dissipation pour div
279  !Config  Def  = 7200
280  !Config  Help = temps de dissipation des plus petites longeur
281  !Config         d'ondes pour u,v (gradiv)
282  tetagdiv = 7200.
283  CALL getin('tetagdiv',tetagdiv)
284
285  !Config  Key  = tetagrot
286  !Config  Desc = temps de dissipation pour grad
287  !Config  Def  = 7200
288  !Config  Help = temps de dissipation des plus petites longeur
289  !Config         d'ondes pour u,v (nxgradrot)
290  tetagrot = 7200.
291  CALL getin('tetagrot',tetagrot)
292
293  !Config  Key  = tetatemp
294  !Config  Desc = temps de dissipation pour h
295  !Config  Def  = 7200
296  !Config  Help =  temps de dissipation des plus petites longeur
297  !Config         d'ondes pour h (divgrad)   
298  tetatemp  = 7200.
299  CALL getin('tetatemp',tetatemp )
300
301  ! Parametres controlant la variation sur la verticale des constantes de
302  ! dissipation.
303  ! Pour le moment actifs uniquement dans la version a 39 niveaux
304  ! avec ok_strato=y
305
306  dissip_factz=4.
307  dissip_deltaz=10.
308  dissip_zref=30.
309  CALL getin('dissip_factz',dissip_factz )
310  CALL getin('dissip_deltaz',dissip_deltaz )
311  CALL getin('dissip_zref',dissip_zref )
312
313  ! ngroup
314  ngroup=3
315  CALL getin('ngroup',ngroup)
316
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).GE. 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        STOP
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).GE. 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        STOP
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).GE. 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        STOP
447     ENDIF
448
449     IF( grossismx.LT.1. )  THEN
450        write(lunout,*) &
451             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
452        STOP
453     ELSE
454        alphax = 1. - 1./ grossismx
455     ENDIF
456
457     IF( grossismy.LT.1. )  THEN
458        write(lunout,*) &
459             'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
460        STOP
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           STOP
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           STOP
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).GE. 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           STOP
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).GE. 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           STOP
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).GE. 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           STOP
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).GE. 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           STOP
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              STOP
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              STOP
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     !Config  Key  = config_inca
604     !Config  Desc = Choix de configuration de INCA
605     !Config  Def  = none
606     !Config  Help = Choix de configuration de INCA :
607     !Config         'none' = sans INCA
608     !Config         'chem' = INCA avec calcul de chemie
609     !Config         'aero' = INCA avec calcul des aerosols
610     config_inca = 'none'
611     CALL getin('config_inca',config_inca)
612
613     !Config  Key  = ok_dynzon
614     !Config  Desc = calcul et sortie des transports
615     !Config  Def  = n
616     !Config  Help = Permet de mettre en route le calcul des transports
617     !Config         
618     ok_dynzon = .FALSE.
619     CALL getin('ok_dynzon',ok_dynzon)
620
621     !Config  Key  = ok_dyn_ins
622     !Config  Desc = sorties instantanees dans la dynamique
623     !Config  Def  = n
624     !Config  Help =
625     !Config         
626     ok_dyn_ins = .FALSE.
627     CALL getin('ok_dyn_ins',ok_dyn_ins)
628
629     !Config  Key  = ok_dyn_ave
630     !Config  Desc = sorties moyennes dans la dynamique
631     !Config  Def  = n
632     !Config  Help =
633     !Config         
634     ok_dyn_ave = .FALSE.
635     CALL getin('ok_dyn_ave',ok_dyn_ave)
636
637     write(lunout,*)' #########################################'
638     write(lunout,*)' Configuration des parametres du gcm: '
639     write(lunout,*)' planet_type = ', planet_type
640     write(lunout,*)' calend = ', calend
641     write(lunout,*)' dayref = ', dayref
642     write(lunout,*)' anneeref = ', anneeref
643     write(lunout,*)' nday = ', nday
644     write(lunout,*)' day_step = ', day_step
645     write(lunout,*)' iperiod = ', iperiod
646     write(lunout,*)' nsplit_phys = ', nsplit_phys
647     write(lunout,*)' iconser = ', iconser
648     write(lunout,*)' iecri = ', iecri
649     write(lunout,*)' periodav = ', periodav
650     write(lunout,*)' output_grads_dyn = ', output_grads_dyn
651     write(lunout,*)' dissip_period = ', dissip_period
652     write(lunout,*)' lstardis = ', lstardis
653     write(lunout,*)' nitergdiv = ', nitergdiv
654     write(lunout,*)' nitergrot = ', nitergrot
655     write(lunout,*)' niterh = ', niterh
656     write(lunout,*)' tetagdiv = ', tetagdiv
657     write(lunout,*)' tetagrot = ', tetagrot
658     write(lunout,*)' tetatemp = ', tetatemp
659     write(lunout,*)' coefdis = ', coefdis
660     write(lunout,*)' purmats = ', purmats
661     write(lunout,*)' read_start = ', read_start
662     write(lunout,*)' iflag_phys = ', iflag_phys
663     write(lunout,*)' iphysiq = ', iphysiq
664     write(lunout,*)' clonn = ', clonn
665     write(lunout,*)' clatt = ', clatt
666     write(lunout,*)' grossismx = ', grossismx
667     write(lunout,*)' grossismy = ', grossismy
668     write(lunout,*)' fxyhypbb = ', fxyhypbb
669     write(lunout,*)' dzoomxx = ', dzoomxx
670     write(lunout,*)' dzoomy = ', dzoomyy
671     write(lunout,*)' tauxx = ', tauxx
672     write(lunout,*)' tauyy = ', tauyy
673     write(lunout,*)' offline = ', offline
674     write(lunout,*)' type_trac = ', type_trac
675     write(lunout,*)' config_inca = ', config_inca
676     write(lunout,*)' ok_dynzon = ', ok_dynzon
677     write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
678     write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
679  else
680     !Config  Key  = clon
681     !Config  Desc = centre du zoom, longitude
682     !Config  Def  = 0
683     !Config  Help = longitude en degres du centre
684     !Config         du zoom
685     clon = 0.
686     CALL getin('clon',clon)
687
688     !Config  Key  = clat
689     !Config  Desc = centre du zoom, latitude
690     !Config  Def  = 0
691     !Config  Help = latitude en degres du centre du zoom
692     !Config         
693     clat = 0.
694     CALL getin('clat',clat)
695
696     !Config  Key  = grossismx
697     !Config  Desc = zoom en longitude
698     !Config  Def  = 1.0
699     !Config  Help = facteur de grossissement du zoom,
700     !Config         selon la longitude
701     grossismx = 1.0
702     CALL getin('grossismx',grossismx)
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     grossismy = 1.0
710     CALL getin('grossismy',grossismy)
711
712     IF( grossismx.LT.1. )  THEN
713        write(lunout,*) &
714             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
715        STOP
716     ELSE
717        alphax = 1. - 1./ grossismx
718     ENDIF
719
720     IF( grossismy.LT.1. )  THEN
721        write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
722        STOP
723     ELSE
724        alphay = 1. - 1./ grossismy
725     ENDIF
726
727     write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
728
729     !    alphax et alphay sont les anciennes formulat. des grossissements
730
731     !Config  Key  = fxyhypb
732     !Config  Desc = Fonction  hyperbolique
733     !Config  Def  = y
734     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
735     !Config         sinon  sinusoidale
736     fxyhypb = .TRUE.
737     CALL getin('fxyhypb',fxyhypb)
738
739     !Config  Key  = dzoomx
740     !Config  Desc = extension en longitude
741     !Config  Def  = 0
742     !Config  Help = extension en longitude  de la zone du zoom 
743     !Config         ( fraction de la zone totale)
744     dzoomx = 0.2
745     CALL getin('dzoomx',dzoomx)
746     call assert(dzoomx < 1, "conf_gcm: dzoomx must be < 1")
747
748     !Config  Key  = dzoomy
749     !Config  Desc = extension en latitude
750     !Config  Def  = 0
751     !Config  Help = extension en latitude de la zone  du zoom 
752     !Config         ( fraction de la zone totale)
753     dzoomy = 0.2
754     CALL getin('dzoomy',dzoomy)
755     call assert(dzoomy < 1, "conf_gcm: dzoomy must be < 1")
756
757     !Config  Key  = taux
758     !Config  Desc = raideur du zoom en  X
759     !Config  Def  = 3
760     !Config  Help = raideur du zoom en  X
761     taux = 3.0
762     CALL getin('taux',taux)
763
764     !Config  Key  = tauy
765     !Config  Desc = raideur du zoom en  Y
766     !Config  Def  = 3
767     !Config  Help = raideur du zoom en  Y
768     tauy = 3.0
769     CALL getin('tauy',tauy)
770
771     !Config  Key  = ysinus
772     !Config  IF   = !fxyhypb
773     !Config  Desc = Fonction en Sinus
774     !Config  Def  = y
775     !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
776     !Config         sinon y = latit.
777     ysinus = .TRUE.
778     CALL getin('ysinus',ysinus)
779
780     !Config  Key  = offline
781     !Config  Desc = Nouvelle eau liquide
782     !Config  Def  = n
783     !Config  Help = Permet de mettre en route la
784     !Config         nouvelle parametrisation de l'eau liquide !
785     offline = .FALSE.
786     CALL getin('offline',offline)
787
788     !Config  Key  = type_trac
789     !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
790     !Config  Def  = lmdz
791     !Config  Help =
792     !Config         'lmdz' = pas de couplage, pur LMDZ
793     !Config         'inca' = model de chime INCA
794     !Config         'repr' = model de chime REPROBUS
795     !Config         'inco' = INCA + CO2i (temporaire)
796     type_trac = 'lmdz'
797     CALL getin('type_trac',type_trac)
798
799     !Config  Key  = config_inca
800     !Config  Desc = Choix de configuration de INCA
801     !Config  Def  = none
802     !Config  Help = Choix de configuration de INCA :
803     !Config         'none' = sans INCA
804     !Config         'chem' = INCA avec calcul de chemie
805     !Config         'aero' = INCA avec calcul des aerosols
806     config_inca = 'none'
807     CALL getin('config_inca',config_inca)
808
809     !Config  Key  = ok_dynzon
810     !Config  Desc = sortie des transports zonaux dans la dynamique
811     !Config  Def  = n
812     !Config  Help = Permet de mettre en route le calcul des transports
813     !Config         
814     ok_dynzon = .FALSE.
815     CALL getin('ok_dynzon',ok_dynzon)
816
817     !Config  Key  = ok_dyn_ins
818     !Config  Desc = sorties instantanees dans la dynamique
819     !Config  Def  = n
820     !Config  Help =
821     !Config         
822     ok_dyn_ins = .FALSE.
823     CALL getin('ok_dyn_ins',ok_dyn_ins)
824
825     !Config  Key  = ok_dyn_ave
826     !Config  Desc = sorties moyennes dans la dynamique
827     !Config  Def  = n
828     !Config  Help =
829     !Config         
830     ok_dyn_ave = .FALSE.
831     CALL getin('ok_dyn_ave',ok_dyn_ave)
832
833     !Config key = ok_strato
834     !Config  Desc = activation de la version strato
835     !Config  Def  = .FALSE.
836     !Config  Help = active la version stratosph\'erique de LMDZ de F. Lott
837
838     ok_strato=.FALSE.
839     CALL getin('ok_strato',ok_strato)
840
841     vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
842     CALL getin('vert_prof_dissip', vert_prof_dissip)
843     call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1, &
844          "bad value for vert_prof_dissip")
845
846     !Config  Key  = ok_gradsfile
847     !Config  Desc = activation des sorties grads du guidage
848     !Config  Def  = n
849     !Config  Help = active les sorties grads du guidage
850
851     ok_gradsfile = .FALSE.
852     CALL getin('ok_gradsfile',ok_gradsfile)
853
854     !Config  Key  = ok_limit
855     !Config  Desc = creation des fichiers limit dans create_etat0_limit
856     !Config  Def  = y
857     !Config  Help = production du fichier limit.nc requise
858
859     ok_limit = .TRUE.
860     CALL getin('ok_limit',ok_limit)
861
862     !Config  Key  = ok_etat0
863     !Config  Desc = creation des fichiers etat0 dans create_etat0_limit
864     !Config  Def  = y
865     !Config  Help = production des fichiers start.nc, startphy.nc requise
866
867     ok_etat0 = .TRUE.
868     CALL getin('ok_etat0',ok_etat0)
869
870     !Config  Key  = read_orop
871     !Config  Desc = lecture du fichier de params orographiques sous maille
872     !Config  Def  = f
873     !Config  Help = lecture fichier plutot que grid_noro
874
875     read_orop = .FALSE.
876     CALL getin('read_orop',read_orop)
877
878     write(lunout,*)' #########################################'
879     write(lunout,*)' Configuration des parametres de cel0' &
880          //'_limit: '
881     write(lunout,*)' planet_type = ', planet_type
882     write(lunout,*)' calend = ', calend
883     write(lunout,*)' dayref = ', dayref
884     write(lunout,*)' anneeref = ', anneeref
885     write(lunout,*)' nday = ', nday
886     write(lunout,*)' day_step = ', day_step
887     write(lunout,*)' iperiod = ', iperiod
888     write(lunout,*)' iconser = ', iconser
889     write(lunout,*)' iecri = ', iecri
890     write(lunout,*)' periodav = ', periodav
891     write(lunout,*)' output_grads_dyn = ', output_grads_dyn
892     write(lunout,*)' dissip_period = ', dissip_period
893     write(lunout,*)' lstardis = ', lstardis
894     write(lunout,*)' nitergdiv = ', nitergdiv
895     write(lunout,*)' nitergrot = ', nitergrot
896     write(lunout,*)' niterh = ', niterh
897     write(lunout,*)' tetagdiv = ', tetagdiv
898     write(lunout,*)' tetagrot = ', tetagrot
899     write(lunout,*)' tetatemp = ', tetatemp
900     write(lunout,*)' coefdis = ', coefdis
901     write(lunout,*)' purmats = ', purmats
902     write(lunout,*)' read_start = ', read_start
903     write(lunout,*)' iflag_phys = ', iflag_phys
904     write(lunout,*)' iphysiq = ', iphysiq
905     write(lunout,*)' clon = ', clon
906     write(lunout,*)' clat = ', clat
907     write(lunout,*)' grossismx = ', grossismx
908     write(lunout,*)' grossismy = ', grossismy
909     write(lunout,*)' fxyhypb = ', fxyhypb
910     write(lunout,*)' dzoomx = ', dzoomx
911     write(lunout,*)' dzoomy = ', dzoomy
912     write(lunout,*)' taux = ', taux
913     write(lunout,*)' tauy = ', tauy
914     write(lunout,*)' offline = ', offline
915     write(lunout,*)' type_trac = ', type_trac
916     write(lunout,*)' config_inca = ', config_inca
917     write(lunout,*)' ok_dynzon = ', ok_dynzon
918     write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
919     write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
920     write(lunout,*)' ok_strato = ', ok_strato
921     write(lunout,*)' ok_gradsfile = ', ok_gradsfile
922     write(lunout,*)' ok_limit = ', ok_limit
923     write(lunout,*)' ok_etat0 = ', ok_etat0
924     write(lunout,*)' read_orop = ', read_orop
925  end IF test_etatinit
926
927END SUBROUTINE conf_gcm
Note: See TracBrowser for help on using the repository browser.