source: LMDZ6/trunk/libf/dyn3d/conf_gcm.f90 @ 5285

Last change on this file since 5285 was 5285, checked in by abarral, 7 hours ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

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