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

Last change on this file since 2302 was 2247, checked in by lguez, 9 years ago

We want to keep the same "*.def" files with programs ce0l and gcm. But
there is only a sequential version of program ce0l, which has not the
FFT filter. So we have to ignore the setting of use_filtre_fft in
program ce0l. Moved the test on use_filtre_fft from procedure conf_gcm
to main units ce0l and gcm.

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