source: LMDZ5/branches/testing/libf/dyn3d/conf_gcm.F90 @ 2160

Last change on this file since 2160 was 2160, checked in by Laurent Fairhead, 10 years ago

Merged trunk changes -r2070:2158 into testing branch. Compilation problems introduced by revision r2155 have been corrected by hand

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