source: LMDZ5/trunk/libf/dyn3d/conf_gcm.F90 @ 2859

Last change on this file since 2859 was 2665, checked in by dcugnet, 8 years ago
  • A (re)startphy.nc file (standard name: "startphy0.nc") can be read by ce0l to get land mask, so mask can be defined (in decreasing priority order) from: 1) "o2a.nc file" if this file is found 2) "startphy0.nc" if this file is found 3) "Relief.nc" otherwise
  • Sub-cell scales parameters for orographic gravity waves can be read from file "oro_params.nc" if the configuration key "read_orop" is TRUE. The effect is to bypass the "grid_noro" routine in ce0l, so that any pre-defined mask (from o2a.nc or startphy0.nc) is then overwritten.
  • The gcm stops if the "limit.nc" records number differs from the current year number of days. A warning is issued in case the gcm calendar does not match the time axis attribute "calendar" (if available) from the "limit.nc" file. This attribute is now added to the "limit.nc" time axis.
  • Few simplifications in grid_noro
  • Few parameters changes in acama_gwd and flott_gwd.
  • Variable d_u can be saved in the outputs.
  • 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
2! $Id: conf_gcm.F90 2665 2016-10-12 12:53:20Z fairhead $
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
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
118  !Config  Key  = dayref
119  !Config  Desc = Jour de l'etat initial
120  !Config  Def  = 1
121  !Config  Help = Jour de l'etat initial ( = 350  si 20 Decembre ,
122  !Config         par expl. ,comme ici ) ... A completer
123  dayref=1
124  CALL getin('dayref', dayref)
125
126  !Config  Key  = anneeref
127  !Config  Desc = Annee de l'etat initial
128  !Config  Def  = 1998
129  !Config  Help = Annee de l'etat  initial
130  !Config         (   avec  4  chiffres   ) ... A completer
131  anneeref = 1998
132  CALL getin('anneeref',anneeref)
133
134  !Config  Key  = raz_date
135  !Config  Desc = Remise a zero de la date initiale
136  !Config  Def  = 0 (pas de remise a zero)
137  !Config  Help = Remise a zero de la date initiale
138  !Config         0 pas de remise a zero, on garde la date du fichier restart
139  !Config         1 prise en compte de la date de gcm.def avec remise a zero
140  !Config         des compteurs de pas de temps
141  raz_date = 0
142  CALL getin('raz_date', raz_date)
143
144  !Config  Key  = resetvarc
145  !Config  Desc = Reinit des variables de controle
146  !Config  Def  = n
147  !Config  Help = Reinit des variables de controle
148  resetvarc = .false.
149  CALL getin('resetvarc',resetvarc)
150
151  !Config  Key  = nday
152  !Config  Desc = Nombre de jours d'integration
153  !Config  Def  = 10
154  !Config  Help = Nombre de jours d'integration
155  !Config         ... On pourait aussi permettre des mois ou des annees !
156  nday = 10
157  CALL getin('nday',nday)
158
159  !Config  Key  = starttime
160  !Config  Desc = Heure de depart de la simulation
161  !Config  Def  = 0
162  !Config  Help = Heure de depart de la simulation
163  !Config         en jour
164  starttime = 0
165  CALL getin('starttime',starttime)
166
167  !Config  Key  = day_step
168  !Config  Desc = nombre de pas par jour
169  !Config  Def  = 240
170  !Config  Help = nombre de pas par jour (multiple de iperiod) (
171  !Config          ici pour  dt = 1 min )
172  day_step = 240
173  CALL getin('day_step',day_step)
174
175  !Config  Key  = nsplit_phys
176  nsplit_phys = 1
177  CALL getin('nsplit_phys',nsplit_phys)
178
179  !Config  Key  = iperiod
180  !Config  Desc = periode pour le pas Matsuno
181  !Config  Def  = 5
182  !Config  Help = periode pour le pas Matsuno (en pas de temps)
183  iperiod = 5
184  CALL getin('iperiod',iperiod)
185
186  !Config  Key  = iapp_tracvl
187  !Config  Desc = frequence du groupement des flux
188  !Config  Def  = iperiod
189  !Config  Help = frequence du groupement des flux (en pas de temps)
190  iapp_tracvl = iperiod
191  CALL getin('iapp_tracvl',iapp_tracvl)
192
193  !Config  Key  = iconser
194  !Config  Desc = periode de sortie des variables de controle
195  !Config  Def  = 240 
196  !Config  Help = periode de sortie des variables de controle
197  !Config         (En pas de temps)
198  iconser = 240 
199  CALL getin('iconser', iconser)
200
201  !Config  Key  = iecri
202  !Config  Desc = periode d'ecriture du fichier histoire
203  !Config  Def  = 1
204  !Config  Help = periode d'ecriture du fichier histoire (en jour)
205  iecri = 1
206  CALL getin('iecri',iecri)
207
208  !Config  Key  = periodav
209  !Config  Desc = periode de stockage fichier histmoy
210  !Config  Def  = 1
211  !Config  Help = periode de stockage fichier histmoy (en jour)
212  periodav = 1.
213  CALL getin('periodav',periodav)
214
215  !Config  Key  = output_grads_dyn
216  !Config  Desc = output dynamics diagnostics in 'dyn.dat' file
217  !Config  Def  = n
218  !Config  Help = output dynamics diagnostics in Grads-readable 'dyn.dat' file
219  output_grads_dyn=.false.
220  CALL getin('output_grads_dyn',output_grads_dyn)
221
222  !Config  Key  = dissip_period
223  !Config  Desc = periode de la dissipation
224  !Config  Def  = 0
225  !Config  Help = periode de la dissipation
226  !Config  dissip_period=0 => la valeur sera calcule dans inidissip       
227  !Config  dissip_period>0 => on prend cette valeur
228  dissip_period = 0
229  CALL getin('dissip_period',dissip_period)
230
231  !cc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
232  !cc
233
234  !Config  Key  = lstardis
235  !Config  Desc = choix de l'operateur de dissipation
236  !Config  Def  = y
237  !Config  Help = choix de l'operateur de dissipation
238  !Config         'y' si on veut star et 'n' si on veut non-start !
239  !Config         Moi y en a pas comprendre !
240  lstardis = .TRUE.
241  CALL getin('lstardis',lstardis)
242
243  !Config  Key  = nitergdiv
244  !Config  Desc = Nombre d'iteration de gradiv
245  !Config  Def  = 1
246  !Config  Help = nombre d'iterations de l'operateur de dissipation
247  !Config         gradiv
248  nitergdiv = 1
249  CALL getin('nitergdiv',nitergdiv)
250
251  !Config  Key  = nitergrot
252  !Config  Desc = nombre d'iterations de nxgradrot
253  !Config  Def  = 2
254  !Config  Help = nombre d'iterations de l'operateur de dissipation 
255  !Config         nxgradrot
256  nitergrot = 2
257  CALL getin('nitergrot',nitergrot)
258
259  !Config  Key  = niterh
260  !Config  Desc = nombre d'iterations de divgrad
261  !Config  Def  = 2
262  !Config  Help = nombre d'iterations de l'operateur de dissipation
263  !Config         divgrad
264  niterh = 2
265  CALL getin('niterh',niterh)
266
267  !Config  Key  = tetagdiv
268  !Config  Desc = temps de dissipation pour div
269  !Config  Def  = 7200
270  !Config  Help = temps de dissipation des plus petites longeur
271  !Config         d'ondes pour u,v (gradiv)
272  tetagdiv = 7200.
273  CALL getin('tetagdiv',tetagdiv)
274
275  !Config  Key  = tetagrot
276  !Config  Desc = temps de dissipation pour grad
277  !Config  Def  = 7200
278  !Config  Help = temps de dissipation des plus petites longeur
279  !Config         d'ondes pour u,v (nxgradrot)
280  tetagrot = 7200.
281  CALL getin('tetagrot',tetagrot)
282
283  !Config  Key  = tetatemp
284  !Config  Desc = temps de dissipation pour h
285  !Config  Def  = 7200
286  !Config  Help =  temps de dissipation des plus petites longeur
287  !Config         d'ondes pour h (divgrad)   
288  tetatemp  = 7200.
289  CALL getin('tetatemp',tetatemp )
290
291  ! Parametres controlant la variation sur la verticale des constantes de
292  ! dissipation.
293  ! Pour le moment actifs uniquement dans la version a 39 niveaux
294  ! avec ok_strato=y
295
296  dissip_factz=4.
297  dissip_deltaz=10.
298  dissip_zref=30.
299  CALL getin('dissip_factz',dissip_factz )
300  CALL getin('dissip_deltaz',dissip_deltaz )
301  CALL getin('dissip_zref',dissip_zref )
302
303  ! ngroup
304  ngroup=3
305  CALL getin('ngroup',ngroup)
306
307
308  ! top_bound sponge: only active if ok_strato=.true. and iflag_top_bound!=0
309  !                   iflag_top_bound=0 for no sponge
310  !                   iflag_top_bound=1 for sponge over 4 topmost layers
311  !                   iflag_top_bound=2 for sponge from top to ~1% of top layer pressure
312  iflag_top_bound=1
313  CALL getin('iflag_top_bound',iflag_top_bound)
314
315  ! mode_top_bound : fields towards which sponge relaxation will be done:
316  !                  mode_top_bound=0: no relaxation
317  !                  mode_top_bound=1: u and v relax towards 0
318  !                  mode_top_bound=2: u and v relax towards their zonal mean
319  !                  mode_top_bound=3: u,v and pot. temp. relax towards their zonal mean
320  mode_top_bound=3
321  CALL getin('mode_top_bound',mode_top_bound)
322
323  ! top_bound sponge : inverse of charactericstic relaxation time scale for sponge
324  tau_top_bound=1.e-5
325  CALL getin('tau_top_bound',tau_top_bound)
326
327  !Config  Key  = coefdis
328  !Config  Desc = coefficient pour gamdissip
329  !Config  Def  = 0
330  !Config  Help = coefficient pour gamdissip 
331  coefdis = 0.
332  CALL getin('coefdis',coefdis)
333
334  !Config  Key  = purmats
335  !Config  Desc = Schema d'integration
336  !Config  Def  = n
337  !Config  Help = Choix du schema d'integration temporel.
338  !Config         y = pure Matsuno sinon c'est du Matsuno-leapfrog
339  purmats = .FALSE.
340  CALL getin('purmats',purmats)
341
342  !Config  Key  = ok_guide
343  !Config  Desc = Guidage
344  !Config  Def  = n
345  !Config  Help = Guidage
346  ok_guide = .FALSE.
347  CALL getin('ok_guide',ok_guide)
348
349  !Config  Key  =  read_start
350  !Config  Desc = Initialize model using a 'start.nc' file
351  !Config  Def  = y
352  !Config  Help = y: intialize dynamical fields using a 'start.nc' file
353  !               n: fields are initialized by 'iniacademic' routine
354  read_start= .true.
355  CALL getin('read_start',read_start)
356
357  !Config  Key  = iflag_phys
358  !Config  Desc = Avec ls physique
359  !Config  Def  = 1
360  !Config  Help = Permet de faire tourner le modele sans
361  !Config         physique.
362  iflag_phys = 1
363  CALL getin('iflag_phys',iflag_phys)
364
365  !Config  Key  =  iphysiq
366  !Config  Desc = Periode de la physique
367  !Config  Def  = 5
368  !Config  Help = Periode de la physique en pas de temps de la dynamique.
369  iphysiq = 5
370  CALL getin('iphysiq', iphysiq)
371
372  !Config  Key  = ip_ebil_dyn
373  !Config  Desc = PRINT level for energy conserv. diag.
374  !Config  Def  = 0
375  !Config  Help = PRINT level for energy conservation diag. ;
376  !               les options suivantes existent :
377  !Config         0 pas de print
378  !Config         1 pas de print
379  !Config         2 print,
380  ip_ebil_dyn = 0
381  CALL getin('ip_ebil_dyn',ip_ebil_dyn)
382
383  !cc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
384  !     .........   (  modif  le 17/04/96 )   .........
385
386  test_etatinit: IF (.not. etatinit) then
387     !Config  Key  = clon
388     !Config  Desc = centre du zoom, longitude
389     !Config  Def  = 0
390     !Config  Help = longitude en degres du centre
391     !Config         du zoom
392     clonn = 0.
393     CALL getin('clon',clonn)
394
395     !Config  Key  = clat
396     !Config  Desc = centre du zoom, latitude
397     !Config  Def  = 0
398     !Config  Help = latitude en degres du centre du zoom
399     !Config         
400     clatt = 0.
401     CALL getin('clat',clatt)
402
403     IF( ABS(clat - clatt).GE. 0.001 )  THEN
404        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def', &
405             ' est differente de celle lue sur le fichier  start '
406        STOP
407     ENDIF
408
409     !Config  Key  = grossismx
410     !Config  Desc = zoom en longitude
411     !Config  Def  = 1.0
412     !Config  Help = facteur de grossissement du zoom,
413     !Config         selon la longitude
414     grossismxx = 1.0
415     CALL getin('grossismx',grossismxx)
416
417     IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
418        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ', &
419             'run.def est differente de celle lue sur le fichier  start '
420        STOP
421     ENDIF
422
423     !Config  Key  = grossismy
424     !Config  Desc = zoom en latitude
425     !Config  Def  = 1.0
426     !Config  Help = facteur de grossissement du zoom,
427     !Config         selon la latitude
428     grossismyy = 1.0
429     CALL getin('grossismy',grossismyy)
430
431     IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
432        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ', &
433             'run.def est differente de celle lue sur le fichier  start '
434        STOP
435     ENDIF
436
437     IF( grossismx.LT.1. )  THEN
438        write(lunout,*) &
439             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
440        STOP
441     ELSE
442        alphax = 1. - 1./ grossismx
443     ENDIF
444
445     IF( grossismy.LT.1. )  THEN
446        write(lunout,*) &
447             'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
448        STOP
449     ELSE
450        alphay = 1. - 1./ grossismy
451     ENDIF
452
453     write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
454
455     !    alphax et alphay sont les anciennes formulat. des grossissements
456
457     !Config  Key  = fxyhypb
458     !Config  Desc = Fonction  hyperbolique
459     !Config  Def  = y
460     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
461     !Config         sinon  sinusoidale
462     fxyhypbb = .TRUE.
463     CALL getin('fxyhypb',fxyhypbb)
464
465     IF( .NOT.fxyhypb )  THEN
466        IF( fxyhypbb )     THEN
467           write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
468           write(lunout,*)' *** fxyhypb lu sur le fichier start est ', &
469                'F alors  qu il est  T  sur  run.def  ***'
470           STOP
471        ENDIF
472     ELSE
473        IF( .NOT.fxyhypbb )   THEN
474           write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
475           write(lunout,*)' ***  fxyhypb lu sur le fichier start est ', &
476                'T alors  qu il est  F  sur  run.def  ****  '
477           STOP
478        ENDIF
479     ENDIF
480
481     !Config  Key  = dzoomx
482     !Config  Desc = extension en longitude
483     !Config  Def  = 0
484     !Config  Help = extension en longitude  de la zone du zoom 
485     !Config         ( fraction de la zone totale)
486     dzoomxx = 0.0
487     CALL getin('dzoomx',dzoomxx)
488
489     IF( fxyhypb )  THEN
490        IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
491           write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ', &
492                'run.def est differente de celle lue sur le fichier  start '
493           STOP
494        ENDIF
495     ENDIF
496
497     !Config  Key  = dzoomy
498     !Config  Desc = extension en latitude
499     !Config  Def  = 0
500     !Config  Help = extension en latitude de la zone  du zoom 
501     !Config         ( fraction de la zone totale)
502     dzoomyy = 0.0
503     CALL getin('dzoomy',dzoomyy)
504
505     IF( fxyhypb )  THEN
506        IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
507           write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ', &
508                'run.def est differente de celle lue sur le fichier  start '
509           STOP
510        ENDIF
511     ENDIF
512
513     !Config  Key  = taux
514     !Config  Desc = raideur du zoom en  X
515     !Config  Def  = 3
516     !Config  Help = raideur du zoom en  X
517     tauxx = 3.0
518     CALL getin('taux',tauxx)
519
520     IF( fxyhypb )  THEN
521        IF( ABS(taux - tauxx).GE. 0.001 )  THEN
522           write(lunout,*)'conf_gcm: La valeur de taux passee par ', &
523                'run.def est differente de celle lue sur le fichier  start '
524           STOP
525        ENDIF
526     ENDIF
527
528     !Config  Key  = tauyy
529     !Config  Desc = raideur du zoom en  Y
530     !Config  Def  = 3
531     !Config  Help = raideur du zoom en  Y
532     tauyy = 3.0
533     CALL getin('tauy',tauyy)
534
535     IF( fxyhypb )  THEN
536        IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
537           write(lunout,*)'conf_gcm: La valeur de tauy passee par ', &
538                'run.def est differente de celle lue sur le fichier  start '
539           STOP
540        ENDIF
541     ENDIF
542
543     !c
544     IF( .NOT.fxyhypb  )  THEN
545
546        !Config  Key  = ysinus
547        !Config  IF   = !fxyhypb
548        !Config  Desc = Fonction en Sinus
549        !Config  Def  = y
550        !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
551        !Config         sinon y = latit.
552        ysinuss = .TRUE.
553        CALL getin('ysinus',ysinuss)
554
555        IF( .NOT.ysinus )  THEN
556           IF( ysinuss )     THEN
557              write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
558              write(lunout,*)' *** ysinus lu sur le fichier start est F', &
559                   ' alors  qu il est  T  sur  run.def  ***'
560              STOP
561           ENDIF
562        ELSE
563           IF( .NOT.ysinuss )   THEN
564              write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
565              write(lunout,*)' *** ysinus lu sur le fichier start est T', &
566                   ' alors  qu il est  F  sur  run.def  ****  '
567              STOP
568           ENDIF
569        ENDIF
570     ENDIF ! of IF( .NOT.fxyhypb  )
571
572     !Config  Key  = offline
573     !Config  Desc = Nouvelle eau liquide
574     !Config  Def  = n
575     !Config  Help = Permet de mettre en route la
576     !Config         nouvelle parametrisation de l'eau liquide !
577     offline = .FALSE.
578     CALL getin('offline',offline)
579
580     !Config  Key  = type_trac
581     !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
582     !Config  Def  = lmdz
583     !Config  Help =
584     !Config         'lmdz' = pas de couplage, pur LMDZ
585     !Config         'inca' = model de chime INCA
586     !Config         'repr' = model de chime REPROBUS
587     type_trac = 'lmdz'
588     CALL getin('type_trac',type_trac)
589
590     !Config  Key  = config_inca
591     !Config  Desc = Choix de configuration de INCA
592     !Config  Def  = none
593     !Config  Help = Choix de configuration de INCA :
594     !Config         'none' = sans INCA
595     !Config         'chem' = INCA avec calcul de chemie
596     !Config         'aero' = INCA avec calcul des aerosols
597     config_inca = 'none'
598     CALL getin('config_inca',config_inca)
599
600     !Config  Key  = ok_dynzon
601     !Config  Desc = calcul et sortie des transports
602     !Config  Def  = n
603     !Config  Help = Permet de mettre en route le calcul des transports
604     !Config         
605     ok_dynzon = .FALSE.
606     CALL getin('ok_dynzon',ok_dynzon)
607
608     !Config  Key  = ok_dyn_ins
609     !Config  Desc = sorties instantanees dans la dynamique
610     !Config  Def  = n
611     !Config  Help =
612     !Config         
613     ok_dyn_ins = .FALSE.
614     CALL getin('ok_dyn_ins',ok_dyn_ins)
615
616     !Config  Key  = ok_dyn_ave
617     !Config  Desc = sorties moyennes dans la dynamique
618     !Config  Def  = n
619     !Config  Help =
620     !Config         
621     ok_dyn_ave = .FALSE.
622     CALL getin('ok_dyn_ave',ok_dyn_ave)
623
624     write(lunout,*)' #########################################'
625     write(lunout,*)' Configuration des parametres du gcm: '
626     write(lunout,*)' planet_type = ', planet_type
627     write(lunout,*)' calend = ', calend
628     write(lunout,*)' dayref = ', dayref
629     write(lunout,*)' anneeref = ', anneeref
630     write(lunout,*)' nday = ', nday
631     write(lunout,*)' day_step = ', day_step
632     write(lunout,*)' iperiod = ', iperiod
633     write(lunout,*)' nsplit_phys = ', nsplit_phys
634     write(lunout,*)' iconser = ', iconser
635     write(lunout,*)' iecri = ', iecri
636     write(lunout,*)' periodav = ', periodav
637     write(lunout,*)' output_grads_dyn = ', output_grads_dyn
638     write(lunout,*)' dissip_period = ', dissip_period
639     write(lunout,*)' lstardis = ', lstardis
640     write(lunout,*)' nitergdiv = ', nitergdiv
641     write(lunout,*)' nitergrot = ', nitergrot
642     write(lunout,*)' niterh = ', niterh
643     write(lunout,*)' tetagdiv = ', tetagdiv
644     write(lunout,*)' tetagrot = ', tetagrot
645     write(lunout,*)' tetatemp = ', tetatemp
646     write(lunout,*)' coefdis = ', coefdis
647     write(lunout,*)' purmats = ', purmats
648     write(lunout,*)' read_start = ', read_start
649     write(lunout,*)' iflag_phys = ', iflag_phys
650     write(lunout,*)' iphysiq = ', iphysiq
651     write(lunout,*)' clonn = ', clonn
652     write(lunout,*)' clatt = ', clatt
653     write(lunout,*)' grossismx = ', grossismx
654     write(lunout,*)' grossismy = ', grossismy
655     write(lunout,*)' fxyhypbb = ', fxyhypbb
656     write(lunout,*)' dzoomxx = ', dzoomxx
657     write(lunout,*)' dzoomy = ', dzoomyy
658     write(lunout,*)' tauxx = ', tauxx
659     write(lunout,*)' tauyy = ', tauyy
660     write(lunout,*)' offline = ', offline
661     write(lunout,*)' type_trac = ', type_trac
662     write(lunout,*)' config_inca = ', config_inca
663     write(lunout,*)' ok_dynzon = ', ok_dynzon
664     write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
665     write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
666  else
667     !Config  Key  = clon
668     !Config  Desc = centre du zoom, longitude
669     !Config  Def  = 0
670     !Config  Help = longitude en degres du centre
671     !Config         du zoom
672     clon = 0.
673     CALL getin('clon',clon)
674
675     !Config  Key  = clat
676     !Config  Desc = centre du zoom, latitude
677     !Config  Def  = 0
678     !Config  Help = latitude en degres du centre du zoom
679     !Config         
680     clat = 0.
681     CALL getin('clat',clat)
682
683     !Config  Key  = grossismx
684     !Config  Desc = zoom en longitude
685     !Config  Def  = 1.0
686     !Config  Help = facteur de grossissement du zoom,
687     !Config         selon la longitude
688     grossismx = 1.0
689     CALL getin('grossismx',grossismx)
690
691     !Config  Key  = grossismy
692     !Config  Desc = zoom en latitude
693     !Config  Def  = 1.0
694     !Config  Help = facteur de grossissement du zoom,
695     !Config         selon la latitude
696     grossismy = 1.0
697     CALL getin('grossismy',grossismy)
698
699     IF( grossismx.LT.1. )  THEN
700        write(lunout,*) &
701             'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
702        STOP
703     ELSE
704        alphax = 1. - 1./ grossismx
705     ENDIF
706
707     IF( grossismy.LT.1. )  THEN
708        write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
709        STOP
710     ELSE
711        alphay = 1. - 1./ grossismy
712     ENDIF
713
714     write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
715
716     !    alphax et alphay sont les anciennes formulat. des grossissements
717
718     !Config  Key  = fxyhypb
719     !Config  Desc = Fonction  hyperbolique
720     !Config  Def  = y
721     !Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
722     !Config         sinon  sinusoidale
723     fxyhypb = .TRUE.
724     CALL getin('fxyhypb',fxyhypb)
725
726     !Config  Key  = dzoomx
727     !Config  Desc = extension en longitude
728     !Config  Def  = 0
729     !Config  Help = extension en longitude  de la zone du zoom 
730     !Config         ( fraction de la zone totale)
731     dzoomx = 0.2
732     CALL getin('dzoomx',dzoomx)
733     call assert(dzoomx < 1, "conf_gcm: dzoomx must be < 1")
734
735     !Config  Key  = dzoomy
736     !Config  Desc = extension en latitude
737     !Config  Def  = 0
738     !Config  Help = extension en latitude de la zone  du zoom 
739     !Config         ( fraction de la zone totale)
740     dzoomy = 0.2
741     CALL getin('dzoomy',dzoomy)
742     call assert(dzoomy < 1, "conf_gcm: dzoomy must be < 1")
743
744     !Config  Key  = taux
745     !Config  Desc = raideur du zoom en  X
746     !Config  Def  = 3
747     !Config  Help = raideur du zoom en  X
748     taux = 3.0
749     CALL getin('taux',taux)
750
751     !Config  Key  = tauy
752     !Config  Desc = raideur du zoom en  Y
753     !Config  Def  = 3
754     !Config  Help = raideur du zoom en  Y
755     tauy = 3.0
756     CALL getin('tauy',tauy)
757
758     !Config  Key  = ysinus
759     !Config  IF   = !fxyhypb
760     !Config  Desc = Fonction en Sinus
761     !Config  Def  = y
762     !Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
763     !Config         sinon y = latit.
764     ysinus = .TRUE.
765     CALL getin('ysinus',ysinus)
766
767     !Config  Key  = offline
768     !Config  Desc = Nouvelle eau liquide
769     !Config  Def  = n
770     !Config  Help = Permet de mettre en route la
771     !Config         nouvelle parametrisation de l'eau liquide !
772     offline = .FALSE.
773     CALL getin('offline',offline)
774
775     !Config  Key  = type_trac
776     !Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
777     !Config  Def  = lmdz
778     !Config  Help =
779     !Config         'lmdz' = pas de couplage, pur LMDZ
780     !Config         'inca' = model de chime INCA
781     !Config         'repr' = model de chime REPROBUS
782     type_trac = 'lmdz'
783     CALL getin('type_trac',type_trac)
784
785     !Config  Key  = config_inca
786     !Config  Desc = Choix de configuration de INCA
787     !Config  Def  = none
788     !Config  Help = Choix de configuration de INCA :
789     !Config         'none' = sans INCA
790     !Config         'chem' = INCA avec calcul de chemie
791     !Config         'aero' = INCA avec calcul des aerosols
792     config_inca = 'none'
793     CALL getin('config_inca',config_inca)
794
795     !Config  Key  = ok_dynzon
796     !Config  Desc = sortie des transports zonaux dans la dynamique
797     !Config  Def  = n
798     !Config  Help = Permet de mettre en route le calcul des transports
799     !Config         
800     ok_dynzon = .FALSE.
801     CALL getin('ok_dynzon',ok_dynzon)
802
803     !Config  Key  = ok_dyn_ins
804     !Config  Desc = sorties instantanees dans la dynamique
805     !Config  Def  = n
806     !Config  Help =
807     !Config         
808     ok_dyn_ins = .FALSE.
809     CALL getin('ok_dyn_ins',ok_dyn_ins)
810
811     !Config  Key  = ok_dyn_ave
812     !Config  Desc = sorties moyennes dans la dynamique
813     !Config  Def  = n
814     !Config  Help =
815     !Config         
816     ok_dyn_ave = .FALSE.
817     CALL getin('ok_dyn_ave',ok_dyn_ave)
818
819     !Config key = ok_strato
820     !Config  Desc = activation de la version strato
821     !Config  Def  = .FALSE.
822     !Config  Help = active la version stratosph\'erique de LMDZ de F. Lott
823
824     ok_strato=.FALSE.
825     CALL getin('ok_strato',ok_strato)
826
827     vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
828     CALL getin('vert_prof_dissip', vert_prof_dissip)
829     call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1, &
830          "bad value for vert_prof_dissip")
831
832     !Config  Key  = ok_gradsfile
833     !Config  Desc = activation des sorties grads du guidage
834     !Config  Def  = n
835     !Config  Help = active les sorties grads du guidage
836
837     ok_gradsfile = .FALSE.
838     CALL getin('ok_gradsfile',ok_gradsfile)
839
840     !Config  Key  = ok_limit
841     !Config  Desc = creation des fichiers limit dans create_etat0_limit
842     !Config  Def  = y
843     !Config  Help = production du fichier limit.nc requise
844
845     ok_limit = .TRUE.
846     CALL getin('ok_limit',ok_limit)
847
848     !Config  Key  = ok_etat0
849     !Config  Desc = creation des fichiers etat0 dans create_etat0_limit
850     !Config  Def  = y
851     !Config  Help = production des fichiers start.nc, startphy.nc requise
852
853     ok_etat0 = .TRUE.
854     CALL getin('ok_etat0',ok_etat0)
855
856     !Config  Key  = read_orop
857     !Config  Desc = lecture du fichier de params orographiques sous maille
858     !Config  Def  = f
859     !Config  Help = lecture fichier plutot que grid_noro
860
861     read_orop = .FALSE.
862     CALL getin('read_orop',read_orop)
863
864     write(lunout,*)' #########################################'
865     write(lunout,*)' Configuration des parametres de cel0' &
866          //'_limit: '
867     write(lunout,*)' planet_type = ', planet_type
868     write(lunout,*)' calend = ', calend
869     write(lunout,*)' dayref = ', dayref
870     write(lunout,*)' anneeref = ', anneeref
871     write(lunout,*)' nday = ', nday
872     write(lunout,*)' day_step = ', day_step
873     write(lunout,*)' iperiod = ', iperiod
874     write(lunout,*)' iconser = ', iconser
875     write(lunout,*)' iecri = ', iecri
876     write(lunout,*)' periodav = ', periodav
877     write(lunout,*)' output_grads_dyn = ', output_grads_dyn
878     write(lunout,*)' dissip_period = ', dissip_period
879     write(lunout,*)' lstardis = ', lstardis
880     write(lunout,*)' nitergdiv = ', nitergdiv
881     write(lunout,*)' nitergrot = ', nitergrot
882     write(lunout,*)' niterh = ', niterh
883     write(lunout,*)' tetagdiv = ', tetagdiv
884     write(lunout,*)' tetagrot = ', tetagrot
885     write(lunout,*)' tetatemp = ', tetatemp
886     write(lunout,*)' coefdis = ', coefdis
887     write(lunout,*)' purmats = ', purmats
888     write(lunout,*)' read_start = ', read_start
889     write(lunout,*)' iflag_phys = ', iflag_phys
890     write(lunout,*)' iphysiq = ', iphysiq
891     write(lunout,*)' clon = ', clon
892     write(lunout,*)' clat = ', clat
893     write(lunout,*)' grossismx = ', grossismx
894     write(lunout,*)' grossismy = ', grossismy
895     write(lunout,*)' fxyhypb = ', fxyhypb
896     write(lunout,*)' dzoomx = ', dzoomx
897     write(lunout,*)' dzoomy = ', dzoomy
898     write(lunout,*)' taux = ', taux
899     write(lunout,*)' tauy = ', tauy
900     write(lunout,*)' offline = ', offline
901     write(lunout,*)' type_trac = ', type_trac
902     write(lunout,*)' config_inca = ', config_inca
903     write(lunout,*)' ok_dynzon = ', ok_dynzon
904     write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
905     write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
906     write(lunout,*)' ok_strato = ', ok_strato
907     write(lunout,*)' ok_gradsfile = ', ok_gradsfile
908     write(lunout,*)' ok_limit = ', ok_limit
909     write(lunout,*)' ok_etat0 = ', ok_etat0
910     write(lunout,*)' read_orop = ', read_orop
911  end IF test_etatinit
912
913END SUBROUTINE conf_gcm
Note: See TracBrowser for help on using the repository browser.