source: LMDZ5/trunk/libf/dyn3d/conf_gcm.F @ 2141

Last change on this file since 2141 was 2141, checked in by lguez, 10 years ago

iphysiq must be a multiple of iperiod: added the test.

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