source: LMDZ5/trunk/libf/dyn3dpar/conf_gcm.F @ 1860

Last change on this file since 1860 was 1860, checked in by Ehouarn Millour, 11 years ago

Implement in dyn3dpar the modifications that were made in the dyn3dmem dynamics (r1858-1859) about setting size of omp_chunk.
EM

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