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

Last change on this file since 2121 was 2083, checked in by Ehouarn Millour, 10 years ago
  • Minor fix in dyn3dpar/leapfrog_p.F , should call geopot_p and not geopot
  • Added a sanity check in iniacademic
  • Added flag "resetvarc" to trigger a reset of initial values in sortvarc
  • Removed "sortvarc0" since the job can now be done with "resetvarc" and having set flag resertvarc to true.

EM

  • 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.9 KB
RevLine 
[524]1!
[1279]2! $Id: conf_gcm.F 2083 2014-07-09 14:43:31Z lguez $
[524]3!
[2019]4!
5!
[524]6      SUBROUTINE conf_gcm( tapedef, etatinit, clesphy0 )
[2019]7!
[1403]8      USE control_mod
[1146]9#ifdef CPP_IOIPSL
[524]10      use IOIPSL
[1146]11#else
12! if not using IOIPSL, we still need to use (a local version of) getin
13      use ioipsl_getincom
14#endif
[1563]15      USE infotrac, ONLY : type_trac
[1697]16      use assert_m, only: assert
17
[524]18      IMPLICIT NONE
[2019]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!
[524]29       LOGICAL etatinit
30       INTEGER tapedef
31
32       INTEGER        longcles
33       PARAMETER(     longcles = 20 )
34       REAL clesphy0( longcles )
[2019]35!
36!   Declarations :
37!   --------------
[524]38#include "dimensions.h"
39#include "paramet.h"
40#include "logic.h"
41#include "serre.h"
42#include "comdissnew.h"
[1279]43#include "temps.h"
44#include "comconst.h"
[956]45
46! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
47! #include "clesphys.h"
[524]48#include "iniprint.h"
[2019]49!
50!
51!   local:
52!   ------
[524]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
[1418]59      LOGICAL use_filtre_fft
[2019]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!   ----------------
[524]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
[2019]97        OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',                     &
[1697]98     &          STATUS='unknown',FORM='formatted')
[524]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
[2019]109!-----------------------------------------------------------------------
110!  Parametres de controle du run:
111!-----------------------------------------------------------------------
[1146]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)
[524]118
[1279]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
[524]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
[2083]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
[524]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
[1577]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
[524]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
[1403]184!Config  Key  = nsplit_phys
185       nsplit_phys = 1
186       CALL getin('nsplit_phys',nsplit_phys)
187
[524]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
[527]197!Config  Def  = iperiod
[524]198!Config  Help = frequence du groupement des flux (en pas de temps)
[527]199       iapp_tracvl = iperiod
[524]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
[1146]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
[1502]232!Config  Key  = dissip_period
[524]233!Config  Desc = periode de la dissipation
[1502]234!Config  Def  = 0
[524]235!Config  Help = periode de la dissipation
[1502]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)
[524]240
[2019]241!cc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
242!cc
[524]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
[1279]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
[1793]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
[1279]320       iflag_top_bound=1
[1793]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
[1279]332       tau_top_bound=1.e-5
333       CALL getin('tau_top_bound',tau_top_bound)
334
[524]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
[2019]357!    ...............................................................
[524]358
[1146]359!Config  Key  =  read_start
360!Config  Desc = Initialize model using a 'start.nc' file
361!Config  Def  = y
362!Config  Help = y: intialize dynamical fields using a 'start.nc' file
363!               n: fields are initialized by 'iniacademic' routine
364       read_start= .true.
365       CALL getin('read_start',read_start)
366
[524]367!Config  Key  = iflag_phys
368!Config  Desc = Avec ls physique
369!Config  Def  = 1
370!Config  Help = Permet de faire tourner le modele sans
371!Config         physique.
372       iflag_phys = 1
373       CALL getin('iflag_phys',iflag_phys)
374
375
376!Config  Key  =  iphysiq
377!Config  Desc = Periode de la physique
378!Config  Def  = 5
379!Config  Help = Periode de la physique en pas de temps de la dynamique.
380       iphysiq = 5
381       CALL getin('iphysiq', iphysiq)
382
[691]383!Config  Key  = ip_ebil_dyn
384!Config  Desc = PRINT level for energy conserv. diag.
385!Config  Def  = 0
386!Config  Help = PRINT level for energy conservation diag. ;
387!               les options suivantes existent :
388!Config         0 pas de print
389!Config         1 pas de print
390!Config         2 print,
391       ip_ebil_dyn = 0
392       CALL getin('ip_ebil_dyn',ip_ebil_dyn)
393!
[524]394
395      DO i = 1, longcles
396       clesphy0(i) = 0.
397      ENDDO
398
[2019]399!cc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
400!     .........   (  modif  le 17/04/96 )   .........
401!
[524]402      IF( etatinit ) GO TO 100
403
404!Config  Key  = clon
405!Config  Desc = centre du zoom, longitude
406!Config  Def  = 0
407!Config  Help = longitude en degres du centre
408!Config         du zoom
409       clonn = 0.
410       CALL getin('clon',clonn)
411
412!Config  Key  = clat
413!Config  Desc = centre du zoom, latitude
414!Config  Def  = 0
415!Config  Help = latitude en degres du centre du zoom
416!Config         
417       clatt = 0.
418       CALL getin('clat',clatt)
419
[2019]420!
421!
[524]422      IF( ABS(clat - clatt).GE. 0.001 )  THEN
[2019]423        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def',     &
[1146]424     &    ' est differente de celle lue sur le fichier  start '
[524]425        STOP
426      ENDIF
427
428!Config  Key  = grossismx
429!Config  Desc = zoom en longitude
430!Config  Def  = 1.0
431!Config  Help = facteur de grossissement du zoom,
432!Config         selon la longitude
433       grossismxx = 1.0
434       CALL getin('grossismx',grossismxx)
435
436
437      IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
[2019]438        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ',       &
[1146]439     &  'run.def est differente de celle lue sur le fichier  start '
[524]440        STOP
441      ENDIF
442
443!Config  Key  = grossismy
444!Config  Desc = zoom en latitude
445!Config  Def  = 1.0
446!Config  Help = facteur de grossissement du zoom,
447!Config         selon la latitude
448       grossismyy = 1.0
449       CALL getin('grossismy',grossismyy)
450
451      IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
[2019]452        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ',        &
[1146]453     & 'run.def est differente de celle lue sur le fichier  start '
[524]454        STOP
455      ENDIF
456     
457      IF( grossismx.LT.1. )  THEN
[2019]458        write(lunout,*)                                                        &
[1146]459     &       'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
[524]460         STOP
461      ELSE
462         alphax = 1. - 1./ grossismx
463      ENDIF
464
465
466      IF( grossismy.LT.1. )  THEN
[2019]467        write(lunout,*)                                                        &
[1146]468     &       'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
[524]469         STOP
470      ELSE
471         alphay = 1. - 1./ grossismy
472      ENDIF
473
[1146]474      write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
[2019]475!
476!    alphax et alphay sont les anciennes formulat. des grossissements
477!
478!
[524]479
480!Config  Key  = fxyhypb
481!Config  Desc = Fonction  hyperbolique
482!Config  Def  = y
483!Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
484!Config         sinon  sinusoidale
485       fxyhypbb = .TRUE.
486       CALL getin('fxyhypb',fxyhypbb)
487
488      IF( .NOT.fxyhypb )  THEN
[1146]489         IF( fxyhypbb )     THEN
490            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
[2019]491            write(lunout,*)' *** fxyhypb lu sur le fichier start est ',     &
492     &       'F alors  qu il est  T  sur  run.def  ***'
[524]493              STOP
[1146]494         ENDIF
[524]495      ELSE
[1146]496         IF( .NOT.fxyhypbb )   THEN
497            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
[2019]498            write(lunout,*)' ***  fxyhypb lu sur le fichier start est ',     &
499     &        'T alors  qu il est  F  sur  run.def  ****  '
[524]500              STOP
[1146]501         ENDIF
[524]502      ENDIF
[2019]503!
[524]504!Config  Key  = dzoomx
505!Config  Desc = extension en longitude
506!Config  Def  = 0
507!Config  Help = extension en longitude  de la zone du zoom 
508!Config         ( fraction de la zone totale)
509       dzoomxx = 0.0
510       CALL getin('dzoomx',dzoomxx)
511
512      IF( fxyhypb )  THEN
513       IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
[2019]514        write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ',         &
515     &  'run.def est differente de celle lue sur le fichier  start '
[524]516        STOP
517       ENDIF
518      ENDIF
519
520!Config  Key  = dzoomy
521!Config  Desc = extension en latitude
522!Config  Def  = 0
523!Config  Help = extension en latitude de la zone  du zoom 
524!Config         ( fraction de la zone totale)
525       dzoomyy = 0.0
526       CALL getin('dzoomy',dzoomyy)
527
528      IF( fxyhypb )  THEN
529       IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
[2019]530        write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ',          &
531     & 'run.def est differente de celle lue sur le fichier  start '
[524]532        STOP
533       ENDIF
534      ENDIF
535     
536!Config  Key  = taux
537!Config  Desc = raideur du zoom en  X
538!Config  Def  = 3
539!Config  Help = raideur du zoom en  X
540       tauxx = 3.0
541       CALL getin('taux',tauxx)
542
543      IF( fxyhypb )  THEN
544       IF( ABS(taux - tauxx).GE. 0.001 )  THEN
[2019]545        write(lunout,*)'conf_gcm: La valeur de taux passee par ',           &
546     & 'run.def est differente de celle lue sur le fichier  start '
[524]547        STOP
548       ENDIF
549      ENDIF
550
551!Config  Key  = tauyy
552!Config  Desc = raideur du zoom en  Y
553!Config  Def  = 3
554!Config  Help = raideur du zoom en  Y
555       tauyy = 3.0
556       CALL getin('tauy',tauyy)
557
558      IF( fxyhypb )  THEN
559       IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
[2019]560        write(lunout,*)'conf_gcm: La valeur de tauy passee par ',           &
561     & 'run.def est differente de celle lue sur le fichier  start '
[524]562        STOP
563       ENDIF
564      ENDIF
565
[2019]566!c
[524]567      IF( .NOT.fxyhypb  )  THEN
568
569!Config  Key  = ysinus
570!Config  IF   = !fxyhypb
571!Config  Desc = Fonction en Sinus
572!Config  Def  = y
573!Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
574!Config         sinon y = latit.
575       ysinuss = .TRUE.
576       CALL getin('ysinus',ysinuss)
577
578        IF( .NOT.ysinus )  THEN
[1146]579          IF( ysinuss )     THEN
580            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
[2019]581            write(lunout,*)' *** ysinus lu sur le fichier start est F',     &
582     &       ' alors  qu il est  T  sur  run.def  ***'
[1146]583            STOP
584          ENDIF
[524]585        ELSE
[1146]586          IF( .NOT.ysinuss )   THEN
587            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
[2019]588            write(lunout,*)' *** ysinus lu sur le fichier start est T',     &
589     &        ' alors  qu il est  F  sur  run.def  ****  '
[524]590              STOP
[1146]591          ENDIF
[524]592        ENDIF
[1146]593      ENDIF ! of IF( .NOT.fxyhypb  )
[2019]594!
[541]595!Config  Key  = offline
596!Config  Desc = Nouvelle eau liquide
597!Config  Def  = n
598!Config  Help = Permet de mettre en route la
599!Config         nouvelle parametrisation de l'eau liquide !
600       offline = .FALSE.
601       CALL getin('offline',offline)
[1563]602     
603!Config  Key  = type_trac
604!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
605!Config  Def  = lmdz
606!Config  Help =
607!Config         'lmdz' = pas de couplage, pur LMDZ
608!Config         'inca' = model de chime INCA
609!Config         'repr' = model de chime REPROBUS
610      type_trac = 'lmdz'
611      CALL getin('type_trac',type_trac)
[524]612
[960]613!Config  Key  = config_inca
614!Config  Desc = Choix de configuration de INCA
615!Config  Def  = none
616!Config  Help = Choix de configuration de INCA :
617!Config         'none' = sans INCA
618!Config         'chem' = INCA avec calcul de chemie
619!Config         'aero' = INCA avec calcul des aerosols
620      config_inca = 'none'
621      CALL getin('config_inca',config_inca)
[541]622
[1146]623!Config  Key  = ok_dynzon
624!Config  Desc = calcul et sortie des transports
625!Config  Def  = n
626!Config  Help = Permet de mettre en route le calcul des transports
627!Config         
628      ok_dynzon = .FALSE.
629      CALL getin('ok_dynzon',ok_dynzon)
630
[1403]631!Config  Key  = ok_dyn_ins
632!Config  Desc = sorties instantanees dans la dynamique
633!Config  Def  = n
634!Config  Help =
635!Config         
636      ok_dyn_ins = .FALSE.
637      CALL getin('ok_dyn_ins',ok_dyn_ins)
638
639!Config  Key  = ok_dyn_ave
640!Config  Desc = sorties moyennes dans la dynamique
641!Config  Def  = n
642!Config  Help =
643!Config         
644      ok_dyn_ave = .FALSE.
645      CALL getin('ok_dyn_ave',ok_dyn_ave)
646
[524]647      write(lunout,*)' #########################################'
648      write(lunout,*)' Configuration des parametres du gcm: '
[1146]649      write(lunout,*)' planet_type = ', planet_type
[1279]650      write(lunout,*)' calend = ', calend
[524]651      write(lunout,*)' dayref = ', dayref
652      write(lunout,*)' anneeref = ', anneeref
653      write(lunout,*)' nday = ', nday
654      write(lunout,*)' day_step = ', day_step
655      write(lunout,*)' iperiod = ', iperiod
[1697]656      write(lunout,*)' nsplit_phys = ', nsplit_phys
[524]657      write(lunout,*)' iconser = ', iconser
658      write(lunout,*)' iecri = ', iecri
659      write(lunout,*)' periodav = ', periodav
[1146]660      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
[1502]661      write(lunout,*)' dissip_period = ', dissip_period
[524]662      write(lunout,*)' lstardis = ', lstardis
663      write(lunout,*)' nitergdiv = ', nitergdiv
664      write(lunout,*)' nitergrot = ', nitergrot
665      write(lunout,*)' niterh = ', niterh
666      write(lunout,*)' tetagdiv = ', tetagdiv
667      write(lunout,*)' tetagrot = ', tetagrot
668      write(lunout,*)' tetatemp = ', tetatemp
669      write(lunout,*)' coefdis = ', coefdis
670      write(lunout,*)' purmats = ', purmats
[1146]671      write(lunout,*)' read_start = ', read_start
[524]672      write(lunout,*)' iflag_phys = ', iflag_phys
673      write(lunout,*)' iphysiq = ', iphysiq
674      write(lunout,*)' clonn = ', clonn
675      write(lunout,*)' clatt = ', clatt
676      write(lunout,*)' grossismx = ', grossismx
677      write(lunout,*)' grossismy = ', grossismy
678      write(lunout,*)' fxyhypbb = ', fxyhypbb
679      write(lunout,*)' dzoomxx = ', dzoomxx
680      write(lunout,*)' dzoomy = ', dzoomyy
681      write(lunout,*)' tauxx = ', tauxx
682      write(lunout,*)' tauyy = ', tauyy
[541]683      write(lunout,*)' offline = ', offline
[1563]684      write(lunout,*)' type_trac = ', type_trac
[960]685      write(lunout,*)' config_inca = ', config_inca
[1146]686      write(lunout,*)' ok_dynzon = ', ok_dynzon
[1403]687      write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
688      write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
[524]689
690      RETURN
[2019]691!   ...............................................
692!
[524]693100   CONTINUE
694!Config  Key  = clon
695!Config  Desc = centre du zoom, longitude
696!Config  Def  = 0
697!Config  Help = longitude en degres du centre
698!Config         du zoom
699       clon = 0.
700       CALL getin('clon',clon)
701
702!Config  Key  = clat
703!Config  Desc = centre du zoom, latitude
704!Config  Def  = 0
705!Config  Help = latitude en degres du centre du zoom
706!Config         
707       clat = 0.
708       CALL getin('clat',clat)
709
710!Config  Key  = grossismx
711!Config  Desc = zoom en longitude
712!Config  Def  = 1.0
713!Config  Help = facteur de grossissement du zoom,
714!Config         selon la longitude
715       grossismx = 1.0
716       CALL getin('grossismx',grossismx)
717
718!Config  Key  = grossismy
719!Config  Desc = zoom en latitude
720!Config  Def  = 1.0
721!Config  Help = facteur de grossissement du zoom,
722!Config         selon la latitude
723       grossismy = 1.0
724       CALL getin('grossismy',grossismy)
725
726      IF( grossismx.LT.1. )  THEN
[2019]727        write(lunout,*)'conf_gcm: ***ATTENTION !! grossismx < 1 . *** '
[524]728         STOP
729      ELSE
730         alphax = 1. - 1./ grossismx
731      ENDIF
732
733
734      IF( grossismy.LT.1. )  THEN
[2019]735        write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
[524]736         STOP
737      ELSE
738         alphay = 1. - 1./ grossismy
739      ENDIF
740
[1146]741      write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
[2019]742!
743!    alphax et alphay sont les anciennes formulat. des grossissements
744!
745!
[524]746
747!Config  Key  = fxyhypb
748!Config  Desc = Fonction  hyperbolique
749!Config  Def  = y
750!Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
751!Config         sinon  sinusoidale
752       fxyhypb = .TRUE.
753       CALL getin('fxyhypb',fxyhypb)
754
755!Config  Key  = dzoomx
756!Config  Desc = extension en longitude
757!Config  Def  = 0
758!Config  Help = extension en longitude  de la zone du zoom 
759!Config         ( fraction de la zone totale)
760       dzoomx = 0.0
761       CALL getin('dzoomx',dzoomx)
762
763!Config  Key  = dzoomy
764!Config  Desc = extension en latitude
765!Config  Def  = 0
766!Config  Help = extension en latitude de la zone  du zoom 
767!Config         ( fraction de la zone totale)
768       dzoomy = 0.0
769       CALL getin('dzoomy',dzoomy)
770
771!Config  Key  = taux
772!Config  Desc = raideur du zoom en  X
773!Config  Def  = 3
774!Config  Help = raideur du zoom en  X
775       taux = 3.0
776       CALL getin('taux',taux)
777
778!Config  Key  = tauy
779!Config  Desc = raideur du zoom en  Y
780!Config  Def  = 3
781!Config  Help = raideur du zoom en  Y
782       tauy = 3.0
783       CALL getin('tauy',tauy)
784
785!Config  Key  = ysinus
786!Config  IF   = !fxyhypb
787!Config  Desc = Fonction en Sinus
788!Config  Def  = y
789!Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
790!Config         sinon y = latit.
791       ysinus = .TRUE.
792       CALL getin('ysinus',ysinus)
[2019]793!
[541]794!Config  Key  = offline
795!Config  Desc = Nouvelle eau liquide
796!Config  Def  = n
797!Config  Help = Permet de mettre en route la
798!Config         nouvelle parametrisation de l'eau liquide !
799       offline = .FALSE.
800       CALL getin('offline',offline)
[524]801
[1563]802!Config  Key  = type_trac
803!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
804!Config  Def  = lmdz
805!Config  Help =
806!Config         'lmdz' = pas de couplage, pur LMDZ
807!Config         'inca' = model de chime INCA
808!Config         'repr' = model de chime REPROBUS
809      type_trac = 'lmdz'
810      CALL getin('type_trac',type_trac)
811
[960]812!Config  Key  = config_inca
813!Config  Desc = Choix de configuration de INCA
814!Config  Def  = none
815!Config  Help = Choix de configuration de INCA :
816!Config         'none' = sans INCA
817!Config         'chem' = INCA avec calcul de chemie
818!Config         'aero' = INCA avec calcul des aerosols
819      config_inca = 'none'
820      CALL getin('config_inca',config_inca)
[541]821
[1146]822!Config  Key  = ok_dynzon
[1403]823!Config  Desc = sortie des transports zonaux dans la dynamique
[1146]824!Config  Def  = n
[1697]825!Config  Help = Permet de mettre en route le calcul des transports
[1146]826!Config         
[1697]827      ok_dynzon = .FALSE.
828      CALL getin('ok_dynzon',ok_dynzon)
[1146]829
[1403]830!Config  Key  = ok_dyn_ins
831!Config  Desc = sorties instantanees dans la dynamique
832!Config  Def  = n
833!Config  Help =
834!Config         
835      ok_dyn_ins = .FALSE.
836      CALL getin('ok_dyn_ins',ok_dyn_ins)
837
838!Config  Key  = ok_dyn_ave
839!Config  Desc = sorties moyennes dans la dynamique
840!Config  Def  = n
841!Config  Help =
842!Config         
843      ok_dyn_ave = .FALSE.
844      CALL getin('ok_dyn_ave',ok_dyn_ave)
845
[1418]846!Config  Key  = use_filtre_fft
847!Config  Desc = flag d'activation des FFT pour le filtre
848!Config  Def  = false
849!Config  Help = permet d'activer l'utilisation des FFT pour effectuer
850!Config         le filtrage aux poles.
851! Le filtre fft n'est pas implemente dans dyn3d
852      use_filtre_fft=.FALSE.
853      CALL getin('use_filtre_fft',use_filtre_fft)
854
855      IF (use_filtre_fft) THEN
856        write(lunout,*)'STOP !!!'
857        write(lunout,*)'use_filtre_fft n est pas implemente dans dyn3d'
[1697]858        STOP 1
[1418]859      ENDIF
860     
[999]861!Config key = ok_strato
862!Config  Desc = activation de la version strato
863!Config  Def  = .FALSE.
864!Config  Help = active la version stratosphérique de LMDZ de F. Lott
865
866      ok_strato=.FALSE.
867      CALL getin('ok_strato',ok_strato)
868
[1697]869      vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
870      CALL getin('vert_prof_dissip', vert_prof_dissip)
[2019]871      call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1,        &
872     &     "bad value for vert_prof_dissip")
[1697]873
[1046]874!Config  Key  = ok_gradsfile
875!Config  Desc = activation des sorties grads du guidage
876!Config  Def  = n
877!Config  Help = active les sorties grads du guidage
878
879       ok_gradsfile = .FALSE.
880       CALL getin('ok_gradsfile',ok_gradsfile)
881
[1319]882!Config  Key  = ok_limit
883!Config  Desc = creation des fichiers limit dans create_etat0_limit
884!Config  Def  = y
885!Config  Help = production du fichier limit.nc requise
886
887       ok_limit = .TRUE.
888       CALL getin('ok_limit',ok_limit)
889
890!Config  Key  = ok_etat0
891!Config  Desc = creation des fichiers etat0 dans create_etat0_limit
892!Config  Def  = y
893!Config  Help = production des fichiers start.nc, startphy.nc requise
894
895      ok_etat0 = .TRUE.
896      CALL getin('ok_etat0',ok_etat0)
897
[524]898      write(lunout,*)' #########################################'
[2019]899      write(lunout,*)' Configuration des parametres de cel0'                &
[1319]900     &             //'_limit: '
[1146]901      write(lunout,*)' planet_type = ', planet_type
[1279]902      write(lunout,*)' calend = ', calend
[524]903      write(lunout,*)' dayref = ', dayref
904      write(lunout,*)' anneeref = ', anneeref
905      write(lunout,*)' nday = ', nday
906      write(lunout,*)' day_step = ', day_step
907      write(lunout,*)' iperiod = ', iperiod
908      write(lunout,*)' iconser = ', iconser
909      write(lunout,*)' iecri = ', iecri
910      write(lunout,*)' periodav = ', periodav
[1146]911      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
[1502]912      write(lunout,*)' dissip_period = ', dissip_period
[524]913      write(lunout,*)' lstardis = ', lstardis
914      write(lunout,*)' nitergdiv = ', nitergdiv
915      write(lunout,*)' nitergrot = ', nitergrot
916      write(lunout,*)' niterh = ', niterh
917      write(lunout,*)' tetagdiv = ', tetagdiv
918      write(lunout,*)' tetagrot = ', tetagrot
919      write(lunout,*)' tetatemp = ', tetatemp
920      write(lunout,*)' coefdis = ', coefdis
921      write(lunout,*)' purmats = ', purmats
[1146]922      write(lunout,*)' read_start = ', read_start
[524]923      write(lunout,*)' iflag_phys = ', iflag_phys
924      write(lunout,*)' iphysiq = ', iphysiq
[1146]925      write(lunout,*)' clon = ', clon
926      write(lunout,*)' clat = ', clat
[524]927      write(lunout,*)' grossismx = ', grossismx
928      write(lunout,*)' grossismy = ', grossismy
[1146]929      write(lunout,*)' fxyhypb = ', fxyhypb
[524]930      write(lunout,*)' dzoomx = ', dzoomx
931      write(lunout,*)' dzoomy = ', dzoomy
932      write(lunout,*)' taux = ', taux
933      write(lunout,*)' tauy = ', tauy
[541]934      write(lunout,*)' offline = ', offline
[1563]935      write(lunout,*)' type_trac = ', type_trac
[960]936      write(lunout,*)' config_inca = ', config_inca
[1146]937      write(lunout,*)' ok_dynzon = ', ok_dynzon
[1403]938      write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
939      write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
[999]940      write(lunout,*)' ok_strato = ', ok_strato
[1046]941      write(lunout,*)' ok_gradsfile = ', ok_gradsfile
[1319]942      write(lunout,*)' ok_limit = ', ok_limit
943      write(lunout,*)' ok_etat0 = ', ok_etat0
[2019]944!
[524]945      RETURN
946      END
Note: See TracBrowser for help on using the repository browser.