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