source: LMDZ5/trunk/libf/dyn3dmem/conf_gcm.F @ 2083

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